{-# language CPP #-}
module Vulkan.Extensions.VK_NV_mesh_shader  ( cmdDrawMeshTasksNV
                                            , cmdDrawMeshTasksIndirectNV
                                            , cmdDrawMeshTasksIndirectCountNV
                                            , PhysicalDeviceMeshShaderFeaturesNV(..)
                                            , PhysicalDeviceMeshShaderPropertiesNV(..)
                                            , DrawMeshTasksIndirectCommandNV(..)
                                            , NV_MESH_SHADER_SPEC_VERSION
                                            , pattern NV_MESH_SHADER_SPEC_VERSION
                                            , NV_MESH_SHADER_EXTENSION_NAME
                                            , pattern NV_MESH_SHADER_EXTENSION_NAME
                                            ) where
import Vulkan.CStruct.Utils (FixedArray)
import Control.Monad (unless)
import Control.Monad.IO.Class (liftIO)
import Foreign.Marshal.Alloc (allocaBytesAligned)
import GHC.IO (throwIO)
import GHC.Ptr (nullFunPtr)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import Control.Monad.IO.Class (MonadIO)
import Data.String (IsString)
import Data.Typeable (Typeable)
import Foreign.Storable (Storable)
import Foreign.Storable (Storable(peek))
import Foreign.Storable (Storable(poke))
import qualified Foreign.Storable (Storable(..))
import GHC.Generics (Generic)
import GHC.IO.Exception (IOErrorType(..))
import GHC.IO.Exception (IOException(..))
import Foreign.Ptr (FunPtr)
import Foreign.Ptr (Ptr)
import Data.Word (Word32)
import Data.Kind (Type)
import Vulkan.CStruct.Utils (advancePtrBytes)
import Vulkan.Core10.BaseType (bool32ToBool)
import Vulkan.Core10.BaseType (boolToBool32)
import Vulkan.CStruct.Utils (lowerArrayPtr)
import Vulkan.NamedType ((:::))
import Vulkan.Core10.BaseType (Bool32)
import Vulkan.Core10.Handles (Buffer)
import Vulkan.Core10.Handles (Buffer(..))
import Vulkan.Core10.Handles (CommandBuffer)
import Vulkan.Core10.Handles (CommandBuffer(..))
import Vulkan.Core10.Handles (CommandBuffer_T)
import Vulkan.Dynamic (DeviceCmds(pVkCmdDrawMeshTasksIndirectCountNV))
import Vulkan.Dynamic (DeviceCmds(pVkCmdDrawMeshTasksIndirectNV))
import Vulkan.Dynamic (DeviceCmds(pVkCmdDrawMeshTasksNV))
import Vulkan.Core10.BaseType (DeviceSize)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Zero (Zero(..))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_MESH_SHADER_FEATURES_NV))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_MESH_SHADER_PROPERTIES_NV))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkCmdDrawMeshTasksNV
  :: FunPtr (Ptr CommandBuffer_T -> Word32 -> Word32 -> IO ()) -> Ptr CommandBuffer_T -> Word32 -> Word32 -> IO ()
cmdDrawMeshTasksNV :: forall io
                    . (MonadIO io)
                   => 
                      
                      CommandBuffer
                   -> 
                      
                      ("taskCount" ::: Word32)
                   -> 
                      ("firstTask" ::: Word32)
                   -> io ()
cmdDrawMeshTasksNV :: CommandBuffer
-> ("taskCount" ::: Word32) -> ("taskCount" ::: Word32) -> io ()
cmdDrawMeshTasksNV commandBuffer :: CommandBuffer
commandBuffer taskCount :: "taskCount" ::: Word32
taskCount firstTask :: "taskCount" ::: Word32
firstTask = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ()) -> IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
  let vkCmdDrawMeshTasksNVPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> ("taskCount" ::: Word32) -> ("taskCount" ::: Word32) -> IO ())
vkCmdDrawMeshTasksNVPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("taskCount" ::: Word32) -> ("taskCount" ::: Word32) -> IO ())
pVkCmdDrawMeshTasksNV (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr CommandBuffer_T
   -> ("taskCount" ::: Word32) -> ("taskCount" ::: Word32) -> IO ())
vkCmdDrawMeshTasksNVPtr FunPtr
  (Ptr CommandBuffer_T
   -> ("taskCount" ::: Word32) -> ("taskCount" ::: Word32) -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("taskCount" ::: Word32) -> ("taskCount" ::: Word32) -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> ("taskCount" ::: Word32) -> ("taskCount" ::: Word32) -> IO ())
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 vkCmdDrawMeshTasksNV is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdDrawMeshTasksNV' :: Ptr CommandBuffer_T
-> ("taskCount" ::: Word32) -> ("taskCount" ::: Word32) -> IO ()
vkCmdDrawMeshTasksNV' = FunPtr
  (Ptr CommandBuffer_T
   -> ("taskCount" ::: Word32) -> ("taskCount" ::: Word32) -> IO ())
-> Ptr CommandBuffer_T
-> ("taskCount" ::: Word32)
-> ("taskCount" ::: Word32)
-> IO ()
mkVkCmdDrawMeshTasksNV FunPtr
  (Ptr CommandBuffer_T
   -> ("taskCount" ::: Word32) -> ("taskCount" ::: Word32) -> IO ())
vkCmdDrawMeshTasksNVPtr
  Ptr CommandBuffer_T
-> ("taskCount" ::: Word32) -> ("taskCount" ::: Word32) -> IO ()
vkCmdDrawMeshTasksNV' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) ("taskCount" ::: Word32
taskCount) ("taskCount" ::: Word32
firstTask)
  () -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> IO ()) -> () -> IO ()
forall a b. (a -> b) -> a -> b
$ ()
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkCmdDrawMeshTasksIndirectNV
  :: FunPtr (Ptr CommandBuffer_T -> Buffer -> DeviceSize -> Word32 -> Word32 -> IO ()) -> Ptr CommandBuffer_T -> Buffer -> DeviceSize -> Word32 -> Word32 -> IO ()
cmdDrawMeshTasksIndirectNV :: forall io
                            . (MonadIO io)
                           => 
                              
                              CommandBuffer
                           -> 
                              Buffer
                           -> 
                              ("offset" ::: DeviceSize)
                           -> 
                              ("drawCount" ::: Word32)
                           -> 
                              ("stride" ::: Word32)
                           -> io ()
cmdDrawMeshTasksIndirectNV :: CommandBuffer
-> Buffer
-> ("offset" ::: DeviceSize)
-> ("taskCount" ::: Word32)
-> ("taskCount" ::: Word32)
-> io ()
cmdDrawMeshTasksIndirectNV commandBuffer :: CommandBuffer
commandBuffer buffer :: Buffer
buffer offset :: "offset" ::: DeviceSize
offset drawCount :: "taskCount" ::: Word32
drawCount stride :: "taskCount" ::: Word32
stride = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ()) -> IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
  let vkCmdDrawMeshTasksIndirectNVPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> Buffer
   -> ("offset" ::: DeviceSize)
   -> ("taskCount" ::: Word32)
   -> ("taskCount" ::: Word32)
   -> IO ())
vkCmdDrawMeshTasksIndirectNVPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> Buffer
      -> ("offset" ::: DeviceSize)
      -> ("taskCount" ::: Word32)
      -> ("taskCount" ::: Word32)
      -> IO ())
pVkCmdDrawMeshTasksIndirectNV (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr CommandBuffer_T
   -> Buffer
   -> ("offset" ::: DeviceSize)
   -> ("taskCount" ::: Word32)
   -> ("taskCount" ::: Word32)
   -> IO ())
vkCmdDrawMeshTasksIndirectNVPtr FunPtr
  (Ptr CommandBuffer_T
   -> Buffer
   -> ("offset" ::: DeviceSize)
   -> ("taskCount" ::: Word32)
   -> ("taskCount" ::: Word32)
   -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T
      -> Buffer
      -> ("offset" ::: DeviceSize)
      -> ("taskCount" ::: Word32)
      -> ("taskCount" ::: Word32)
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> Buffer
   -> ("offset" ::: DeviceSize)
   -> ("taskCount" ::: Word32)
   -> ("taskCount" ::: Word32)
   -> IO ())
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 vkCmdDrawMeshTasksIndirectNV is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdDrawMeshTasksIndirectNV' :: Ptr CommandBuffer_T
-> Buffer
-> ("offset" ::: DeviceSize)
-> ("taskCount" ::: Word32)
-> ("taskCount" ::: Word32)
-> IO ()
vkCmdDrawMeshTasksIndirectNV' = FunPtr
  (Ptr CommandBuffer_T
   -> Buffer
   -> ("offset" ::: DeviceSize)
   -> ("taskCount" ::: Word32)
   -> ("taskCount" ::: Word32)
   -> IO ())
-> Ptr CommandBuffer_T
-> Buffer
-> ("offset" ::: DeviceSize)
-> ("taskCount" ::: Word32)
-> ("taskCount" ::: Word32)
-> IO ()
mkVkCmdDrawMeshTasksIndirectNV FunPtr
  (Ptr CommandBuffer_T
   -> Buffer
   -> ("offset" ::: DeviceSize)
   -> ("taskCount" ::: Word32)
   -> ("taskCount" ::: Word32)
   -> IO ())
vkCmdDrawMeshTasksIndirectNVPtr
  Ptr CommandBuffer_T
-> Buffer
-> ("offset" ::: DeviceSize)
-> ("taskCount" ::: Word32)
-> ("taskCount" ::: Word32)
-> IO ()
vkCmdDrawMeshTasksIndirectNV' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) (Buffer
buffer) ("offset" ::: DeviceSize
offset) ("taskCount" ::: Word32
drawCount) ("taskCount" ::: Word32
stride)
  () -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> IO ()) -> () -> IO ()
forall a b. (a -> b) -> a -> b
$ ()
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkCmdDrawMeshTasksIndirectCountNV
  :: FunPtr (Ptr CommandBuffer_T -> Buffer -> DeviceSize -> Buffer -> DeviceSize -> Word32 -> Word32 -> IO ()) -> Ptr CommandBuffer_T -> Buffer -> DeviceSize -> Buffer -> DeviceSize -> Word32 -> Word32 -> IO ()
cmdDrawMeshTasksIndirectCountNV :: forall io
                                 . (MonadIO io)
                                => 
                                   
                                   CommandBuffer
                                -> 
                                   Buffer
                                -> 
                                   ("offset" ::: DeviceSize)
                                -> 
                                   ("countBuffer" ::: Buffer)
                                -> 
                                   
                                   ("countBufferOffset" ::: DeviceSize)
                                -> 
                                   
                                   
                                   ("maxDrawCount" ::: Word32)
                                -> 
                                   ("stride" ::: Word32)
                                -> io ()
cmdDrawMeshTasksIndirectCountNV :: CommandBuffer
-> Buffer
-> ("offset" ::: DeviceSize)
-> Buffer
-> ("offset" ::: DeviceSize)
-> ("taskCount" ::: Word32)
-> ("taskCount" ::: Word32)
-> io ()
cmdDrawMeshTasksIndirectCountNV commandBuffer :: CommandBuffer
commandBuffer buffer :: Buffer
buffer offset :: "offset" ::: DeviceSize
offset countBuffer :: Buffer
countBuffer countBufferOffset :: "offset" ::: DeviceSize
countBufferOffset maxDrawCount :: "taskCount" ::: Word32
maxDrawCount stride :: "taskCount" ::: Word32
stride = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ()) -> IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
  let vkCmdDrawMeshTasksIndirectCountNVPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> Buffer
   -> ("offset" ::: DeviceSize)
   -> Buffer
   -> ("offset" ::: DeviceSize)
   -> ("taskCount" ::: Word32)
   -> ("taskCount" ::: Word32)
   -> IO ())
vkCmdDrawMeshTasksIndirectCountNVPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> Buffer
      -> ("offset" ::: DeviceSize)
      -> Buffer
      -> ("offset" ::: DeviceSize)
      -> ("taskCount" ::: Word32)
      -> ("taskCount" ::: Word32)
      -> IO ())
pVkCmdDrawMeshTasksIndirectCountNV (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr CommandBuffer_T
   -> Buffer
   -> ("offset" ::: DeviceSize)
   -> Buffer
   -> ("offset" ::: DeviceSize)
   -> ("taskCount" ::: Word32)
   -> ("taskCount" ::: Word32)
   -> IO ())
vkCmdDrawMeshTasksIndirectCountNVPtr FunPtr
  (Ptr CommandBuffer_T
   -> Buffer
   -> ("offset" ::: DeviceSize)
   -> Buffer
   -> ("offset" ::: DeviceSize)
   -> ("taskCount" ::: Word32)
   -> ("taskCount" ::: Word32)
   -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T
      -> Buffer
      -> ("offset" ::: DeviceSize)
      -> Buffer
      -> ("offset" ::: DeviceSize)
      -> ("taskCount" ::: Word32)
      -> ("taskCount" ::: Word32)
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> Buffer
   -> ("offset" ::: DeviceSize)
   -> Buffer
   -> ("offset" ::: DeviceSize)
   -> ("taskCount" ::: Word32)
   -> ("taskCount" ::: Word32)
   -> IO ())
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 vkCmdDrawMeshTasksIndirectCountNV is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdDrawMeshTasksIndirectCountNV' :: Ptr CommandBuffer_T
-> Buffer
-> ("offset" ::: DeviceSize)
-> Buffer
-> ("offset" ::: DeviceSize)
-> ("taskCount" ::: Word32)
-> ("taskCount" ::: Word32)
-> IO ()
vkCmdDrawMeshTasksIndirectCountNV' = FunPtr
  (Ptr CommandBuffer_T
   -> Buffer
   -> ("offset" ::: DeviceSize)
   -> Buffer
   -> ("offset" ::: DeviceSize)
   -> ("taskCount" ::: Word32)
   -> ("taskCount" ::: Word32)
   -> IO ())
-> Ptr CommandBuffer_T
-> Buffer
-> ("offset" ::: DeviceSize)
-> Buffer
-> ("offset" ::: DeviceSize)
-> ("taskCount" ::: Word32)
-> ("taskCount" ::: Word32)
-> IO ()
mkVkCmdDrawMeshTasksIndirectCountNV FunPtr
  (Ptr CommandBuffer_T
   -> Buffer
   -> ("offset" ::: DeviceSize)
   -> Buffer
   -> ("offset" ::: DeviceSize)
   -> ("taskCount" ::: Word32)
   -> ("taskCount" ::: Word32)
   -> IO ())
vkCmdDrawMeshTasksIndirectCountNVPtr
  Ptr CommandBuffer_T
-> Buffer
-> ("offset" ::: DeviceSize)
-> Buffer
-> ("offset" ::: DeviceSize)
-> ("taskCount" ::: Word32)
-> ("taskCount" ::: Word32)
-> IO ()
vkCmdDrawMeshTasksIndirectCountNV' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) (Buffer
buffer) ("offset" ::: DeviceSize
offset) (Buffer
countBuffer) ("offset" ::: DeviceSize
countBufferOffset) ("taskCount" ::: Word32
maxDrawCount) ("taskCount" ::: Word32
stride)
  () -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> IO ()) -> () -> IO ()
forall a b. (a -> b) -> a -> b
$ ()
data PhysicalDeviceMeshShaderFeaturesNV = PhysicalDeviceMeshShaderFeaturesNV
  { 
    PhysicalDeviceMeshShaderFeaturesNV -> Bool
taskShader :: Bool
  , 
    PhysicalDeviceMeshShaderFeaturesNV -> Bool
meshShader :: Bool
  }
  deriving (Typeable, PhysicalDeviceMeshShaderFeaturesNV
-> PhysicalDeviceMeshShaderFeaturesNV -> Bool
(PhysicalDeviceMeshShaderFeaturesNV
 -> PhysicalDeviceMeshShaderFeaturesNV -> Bool)
-> (PhysicalDeviceMeshShaderFeaturesNV
    -> PhysicalDeviceMeshShaderFeaturesNV -> Bool)
-> Eq PhysicalDeviceMeshShaderFeaturesNV
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceMeshShaderFeaturesNV
-> PhysicalDeviceMeshShaderFeaturesNV -> Bool
$c/= :: PhysicalDeviceMeshShaderFeaturesNV
-> PhysicalDeviceMeshShaderFeaturesNV -> Bool
== :: PhysicalDeviceMeshShaderFeaturesNV
-> PhysicalDeviceMeshShaderFeaturesNV -> Bool
$c== :: PhysicalDeviceMeshShaderFeaturesNV
-> PhysicalDeviceMeshShaderFeaturesNV -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceMeshShaderFeaturesNV)
#endif
deriving instance Show PhysicalDeviceMeshShaderFeaturesNV
instance ToCStruct PhysicalDeviceMeshShaderFeaturesNV where
  withCStruct :: PhysicalDeviceMeshShaderFeaturesNV
-> (Ptr PhysicalDeviceMeshShaderFeaturesNV -> IO b) -> IO b
withCStruct x :: PhysicalDeviceMeshShaderFeaturesNV
x f :: Ptr PhysicalDeviceMeshShaderFeaturesNV -> IO b
f = Int
-> Int -> (Ptr PhysicalDeviceMeshShaderFeaturesNV -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 8 ((Ptr PhysicalDeviceMeshShaderFeaturesNV -> IO b) -> IO b)
-> (Ptr PhysicalDeviceMeshShaderFeaturesNV -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr PhysicalDeviceMeshShaderFeaturesNV
p -> Ptr PhysicalDeviceMeshShaderFeaturesNV
-> PhysicalDeviceMeshShaderFeaturesNV -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceMeshShaderFeaturesNV
p PhysicalDeviceMeshShaderFeaturesNV
x (Ptr PhysicalDeviceMeshShaderFeaturesNV -> IO b
f Ptr PhysicalDeviceMeshShaderFeaturesNV
p)
  pokeCStruct :: Ptr PhysicalDeviceMeshShaderFeaturesNV
-> PhysicalDeviceMeshShaderFeaturesNV -> IO b -> IO b
pokeCStruct p :: Ptr PhysicalDeviceMeshShaderFeaturesNV
p PhysicalDeviceMeshShaderFeaturesNV{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMeshShaderFeaturesNV
p Ptr PhysicalDeviceMeshShaderFeaturesNV -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_MESH_SHADER_FEATURES_NV)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMeshShaderFeaturesNV
p Ptr PhysicalDeviceMeshShaderFeaturesNV -> 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 PhysicalDeviceMeshShaderFeaturesNV
p Ptr PhysicalDeviceMeshShaderFeaturesNV -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
taskShader))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMeshShaderFeaturesNV
p Ptr PhysicalDeviceMeshShaderFeaturesNV -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
meshShader))
    IO b
f
  cStructSize :: Int
cStructSize = 24
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr PhysicalDeviceMeshShaderFeaturesNV -> IO b -> IO b
pokeZeroCStruct p :: Ptr PhysicalDeviceMeshShaderFeaturesNV
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMeshShaderFeaturesNV
p Ptr PhysicalDeviceMeshShaderFeaturesNV -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_MESH_SHADER_FEATURES_NV)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMeshShaderFeaturesNV
p Ptr PhysicalDeviceMeshShaderFeaturesNV -> 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 PhysicalDeviceMeshShaderFeaturesNV
p Ptr PhysicalDeviceMeshShaderFeaturesNV -> 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 PhysicalDeviceMeshShaderFeaturesNV
p Ptr PhysicalDeviceMeshShaderFeaturesNV -> 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 PhysicalDeviceMeshShaderFeaturesNV where
  peekCStruct :: Ptr PhysicalDeviceMeshShaderFeaturesNV
-> IO PhysicalDeviceMeshShaderFeaturesNV
peekCStruct p :: Ptr PhysicalDeviceMeshShaderFeaturesNV
p = do
    Bool32
taskShader <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceMeshShaderFeaturesNV
p Ptr PhysicalDeviceMeshShaderFeaturesNV -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32))
    Bool32
meshShader <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceMeshShaderFeaturesNV
p Ptr PhysicalDeviceMeshShaderFeaturesNV -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Bool32))
    PhysicalDeviceMeshShaderFeaturesNV
-> IO PhysicalDeviceMeshShaderFeaturesNV
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDeviceMeshShaderFeaturesNV
 -> IO PhysicalDeviceMeshShaderFeaturesNV)
-> PhysicalDeviceMeshShaderFeaturesNV
-> IO PhysicalDeviceMeshShaderFeaturesNV
forall a b. (a -> b) -> a -> b
$ Bool -> Bool -> PhysicalDeviceMeshShaderFeaturesNV
PhysicalDeviceMeshShaderFeaturesNV
             (Bool32 -> Bool
bool32ToBool Bool32
taskShader) (Bool32 -> Bool
bool32ToBool Bool32
meshShader)
instance Storable PhysicalDeviceMeshShaderFeaturesNV where
  sizeOf :: PhysicalDeviceMeshShaderFeaturesNV -> Int
sizeOf ~PhysicalDeviceMeshShaderFeaturesNV
_ = 24
  alignment :: PhysicalDeviceMeshShaderFeaturesNV -> Int
alignment ~PhysicalDeviceMeshShaderFeaturesNV
_ = 8
  peek :: Ptr PhysicalDeviceMeshShaderFeaturesNV
-> IO PhysicalDeviceMeshShaderFeaturesNV
peek = Ptr PhysicalDeviceMeshShaderFeaturesNV
-> IO PhysicalDeviceMeshShaderFeaturesNV
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: Ptr PhysicalDeviceMeshShaderFeaturesNV
-> PhysicalDeviceMeshShaderFeaturesNV -> IO ()
poke ptr :: Ptr PhysicalDeviceMeshShaderFeaturesNV
ptr poked :: PhysicalDeviceMeshShaderFeaturesNV
poked = Ptr PhysicalDeviceMeshShaderFeaturesNV
-> PhysicalDeviceMeshShaderFeaturesNV -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceMeshShaderFeaturesNV
ptr PhysicalDeviceMeshShaderFeaturesNV
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PhysicalDeviceMeshShaderFeaturesNV where
  zero :: PhysicalDeviceMeshShaderFeaturesNV
zero = Bool -> Bool -> PhysicalDeviceMeshShaderFeaturesNV
PhysicalDeviceMeshShaderFeaturesNV
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
data PhysicalDeviceMeshShaderPropertiesNV = PhysicalDeviceMeshShaderPropertiesNV
  { 
    
    
    PhysicalDeviceMeshShaderPropertiesNV -> "taskCount" ::: Word32
maxDrawMeshTasksCount :: Word32
  , 
    
    
    
    
    PhysicalDeviceMeshShaderPropertiesNV -> "taskCount" ::: Word32
maxTaskWorkGroupInvocations :: Word32
  , 
    
    
    
    
    
    PhysicalDeviceMeshShaderPropertiesNV
-> ("taskCount" ::: Word32, "taskCount" ::: Word32,
    "taskCount" ::: Word32)
maxTaskWorkGroupSize :: (Word32, Word32, Word32)
  , 
    
    PhysicalDeviceMeshShaderPropertiesNV -> "taskCount" ::: Word32
maxTaskTotalMemorySize :: Word32
  , 
    
    PhysicalDeviceMeshShaderPropertiesNV -> "taskCount" ::: Word32
maxTaskOutputCount :: Word32
  , 
    
    
    
    
    PhysicalDeviceMeshShaderPropertiesNV -> "taskCount" ::: Word32
maxMeshWorkGroupInvocations :: Word32
  , 
    
    
    
    
    
    PhysicalDeviceMeshShaderPropertiesNV
-> ("taskCount" ::: Word32, "taskCount" ::: Word32,
    "taskCount" ::: Word32)
maxMeshWorkGroupSize :: (Word32, Word32, Word32)
  , 
    
    PhysicalDeviceMeshShaderPropertiesNV -> "taskCount" ::: Word32
maxMeshTotalMemorySize :: Word32
  , 
    
    PhysicalDeviceMeshShaderPropertiesNV -> "taskCount" ::: Word32
maxMeshOutputVertices :: Word32
  , 
    
    PhysicalDeviceMeshShaderPropertiesNV -> "taskCount" ::: Word32
maxMeshOutputPrimitives :: Word32
  , 
    
    PhysicalDeviceMeshShaderPropertiesNV -> "taskCount" ::: Word32
maxMeshMultiviewViewCount :: Word32
  , 
    
    
    
    PhysicalDeviceMeshShaderPropertiesNV -> "taskCount" ::: Word32
meshOutputPerVertexGranularity :: Word32
  , 
    
    
    
    PhysicalDeviceMeshShaderPropertiesNV -> "taskCount" ::: Word32
meshOutputPerPrimitiveGranularity :: Word32
  }
  deriving (Typeable, PhysicalDeviceMeshShaderPropertiesNV
-> PhysicalDeviceMeshShaderPropertiesNV -> Bool
(PhysicalDeviceMeshShaderPropertiesNV
 -> PhysicalDeviceMeshShaderPropertiesNV -> Bool)
-> (PhysicalDeviceMeshShaderPropertiesNV
    -> PhysicalDeviceMeshShaderPropertiesNV -> Bool)
-> Eq PhysicalDeviceMeshShaderPropertiesNV
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceMeshShaderPropertiesNV
-> PhysicalDeviceMeshShaderPropertiesNV -> Bool
$c/= :: PhysicalDeviceMeshShaderPropertiesNV
-> PhysicalDeviceMeshShaderPropertiesNV -> Bool
== :: PhysicalDeviceMeshShaderPropertiesNV
-> PhysicalDeviceMeshShaderPropertiesNV -> Bool
$c== :: PhysicalDeviceMeshShaderPropertiesNV
-> PhysicalDeviceMeshShaderPropertiesNV -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceMeshShaderPropertiesNV)
#endif
deriving instance Show PhysicalDeviceMeshShaderPropertiesNV
instance ToCStruct PhysicalDeviceMeshShaderPropertiesNV where
  withCStruct :: PhysicalDeviceMeshShaderPropertiesNV
-> (Ptr PhysicalDeviceMeshShaderPropertiesNV -> IO b) -> IO b
withCStruct x :: PhysicalDeviceMeshShaderPropertiesNV
x f :: Ptr PhysicalDeviceMeshShaderPropertiesNV -> IO b
f = Int
-> Int
-> (Ptr PhysicalDeviceMeshShaderPropertiesNV -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 88 8 ((Ptr PhysicalDeviceMeshShaderPropertiesNV -> IO b) -> IO b)
-> (Ptr PhysicalDeviceMeshShaderPropertiesNV -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr PhysicalDeviceMeshShaderPropertiesNV
p -> Ptr PhysicalDeviceMeshShaderPropertiesNV
-> PhysicalDeviceMeshShaderPropertiesNV -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceMeshShaderPropertiesNV
p PhysicalDeviceMeshShaderPropertiesNV
x (Ptr PhysicalDeviceMeshShaderPropertiesNV -> IO b
f Ptr PhysicalDeviceMeshShaderPropertiesNV
p)
  pokeCStruct :: Ptr PhysicalDeviceMeshShaderPropertiesNV
-> PhysicalDeviceMeshShaderPropertiesNV -> IO b -> IO b
pokeCStruct p :: Ptr PhysicalDeviceMeshShaderPropertiesNV
p PhysicalDeviceMeshShaderPropertiesNV{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMeshShaderPropertiesNV
p Ptr PhysicalDeviceMeshShaderPropertiesNV
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_MESH_SHADER_PROPERTIES_NV)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMeshShaderPropertiesNV
p Ptr PhysicalDeviceMeshShaderPropertiesNV -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr ("taskCount" ::: Word32) -> ("taskCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMeshShaderPropertiesNV
p Ptr PhysicalDeviceMeshShaderPropertiesNV
-> Int -> Ptr ("taskCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32)) ("taskCount" ::: Word32
maxDrawMeshTasksCount)
    Ptr ("taskCount" ::: Word32) -> ("taskCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMeshShaderPropertiesNV
p Ptr PhysicalDeviceMeshShaderPropertiesNV
-> Int -> Ptr ("taskCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32)) ("taskCount" ::: Word32
maxTaskWorkGroupInvocations)
    let pMaxTaskWorkGroupSize' :: Ptr ("taskCount" ::: Word32)
pMaxTaskWorkGroupSize' = Ptr (FixedArray 3 ("taskCount" ::: Word32))
-> Ptr ("taskCount" ::: Word32)
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr ((Ptr PhysicalDeviceMeshShaderPropertiesNV
p Ptr PhysicalDeviceMeshShaderPropertiesNV
-> Int -> Ptr (FixedArray 3 ("taskCount" ::: Word32))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (FixedArray 3 Word32)))
    case (("taskCount" ::: Word32, "taskCount" ::: Word32,
 "taskCount" ::: Word32)
maxTaskWorkGroupSize) of
      (e0 :: "taskCount" ::: Word32
e0, e1 :: "taskCount" ::: Word32
e1, e2 :: "taskCount" ::: Word32
e2) -> do
        Ptr ("taskCount" ::: Word32) -> ("taskCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ("taskCount" ::: Word32)
pMaxTaskWorkGroupSize' :: Ptr Word32) ("taskCount" ::: Word32
e0)
        Ptr ("taskCount" ::: Word32) -> ("taskCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ("taskCount" ::: Word32)
pMaxTaskWorkGroupSize' Ptr ("taskCount" ::: Word32) -> Int -> Ptr ("taskCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32) ("taskCount" ::: Word32
e1)
        Ptr ("taskCount" ::: Word32) -> ("taskCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ("taskCount" ::: Word32)
pMaxTaskWorkGroupSize' Ptr ("taskCount" ::: Word32) -> Int -> Ptr ("taskCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Word32) ("taskCount" ::: Word32
e2)
    Ptr ("taskCount" ::: Word32) -> ("taskCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMeshShaderPropertiesNV
p Ptr PhysicalDeviceMeshShaderPropertiesNV
-> Int -> Ptr ("taskCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 36 :: Ptr Word32)) ("taskCount" ::: Word32
maxTaskTotalMemorySize)
    Ptr ("taskCount" ::: Word32) -> ("taskCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMeshShaderPropertiesNV
p Ptr PhysicalDeviceMeshShaderPropertiesNV
-> Int -> Ptr ("taskCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr Word32)) ("taskCount" ::: Word32
maxTaskOutputCount)
    Ptr ("taskCount" ::: Word32) -> ("taskCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMeshShaderPropertiesNV
p Ptr PhysicalDeviceMeshShaderPropertiesNV
-> Int -> Ptr ("taskCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 44 :: Ptr Word32)) ("taskCount" ::: Word32
maxMeshWorkGroupInvocations)
    let pMaxMeshWorkGroupSize' :: Ptr ("taskCount" ::: Word32)
pMaxMeshWorkGroupSize' = Ptr (FixedArray 3 ("taskCount" ::: Word32))
-> Ptr ("taskCount" ::: Word32)
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr ((Ptr PhysicalDeviceMeshShaderPropertiesNV
p Ptr PhysicalDeviceMeshShaderPropertiesNV
-> Int -> Ptr (FixedArray 3 ("taskCount" ::: Word32))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr (FixedArray 3 Word32)))
    case (("taskCount" ::: Word32, "taskCount" ::: Word32,
 "taskCount" ::: Word32)
maxMeshWorkGroupSize) of
      (e0 :: "taskCount" ::: Word32
e0, e1 :: "taskCount" ::: Word32
e1, e2 :: "taskCount" ::: Word32
e2) -> do
        Ptr ("taskCount" ::: Word32) -> ("taskCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ("taskCount" ::: Word32)
pMaxMeshWorkGroupSize' :: Ptr Word32) ("taskCount" ::: Word32
e0)
        Ptr ("taskCount" ::: Word32) -> ("taskCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ("taskCount" ::: Word32)
pMaxMeshWorkGroupSize' Ptr ("taskCount" ::: Word32) -> Int -> Ptr ("taskCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32) ("taskCount" ::: Word32
e1)
        Ptr ("taskCount" ::: Word32) -> ("taskCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ("taskCount" ::: Word32)
pMaxMeshWorkGroupSize' Ptr ("taskCount" ::: Word32) -> Int -> Ptr ("taskCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Word32) ("taskCount" ::: Word32
e2)
    Ptr ("taskCount" ::: Word32) -> ("taskCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMeshShaderPropertiesNV
p Ptr PhysicalDeviceMeshShaderPropertiesNV
-> Int -> Ptr ("taskCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 60 :: Ptr Word32)) ("taskCount" ::: Word32
maxMeshTotalMemorySize)
    Ptr ("taskCount" ::: Word32) -> ("taskCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMeshShaderPropertiesNV
p Ptr PhysicalDeviceMeshShaderPropertiesNV
-> Int -> Ptr ("taskCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64 :: Ptr Word32)) ("taskCount" ::: Word32
maxMeshOutputVertices)
    Ptr ("taskCount" ::: Word32) -> ("taskCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMeshShaderPropertiesNV
p Ptr PhysicalDeviceMeshShaderPropertiesNV
-> Int -> Ptr ("taskCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 68 :: Ptr Word32)) ("taskCount" ::: Word32
maxMeshOutputPrimitives)
    Ptr ("taskCount" ::: Word32) -> ("taskCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMeshShaderPropertiesNV
p Ptr PhysicalDeviceMeshShaderPropertiesNV
-> Int -> Ptr ("taskCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 72 :: Ptr Word32)) ("taskCount" ::: Word32
maxMeshMultiviewViewCount)
    Ptr ("taskCount" ::: Word32) -> ("taskCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMeshShaderPropertiesNV
p Ptr PhysicalDeviceMeshShaderPropertiesNV
-> Int -> Ptr ("taskCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 76 :: Ptr Word32)) ("taskCount" ::: Word32
meshOutputPerVertexGranularity)
    Ptr ("taskCount" ::: Word32) -> ("taskCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMeshShaderPropertiesNV
p Ptr PhysicalDeviceMeshShaderPropertiesNV
-> Int -> Ptr ("taskCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 80 :: Ptr Word32)) ("taskCount" ::: Word32
meshOutputPerPrimitiveGranularity)
    IO b
f
  cStructSize :: Int
cStructSize = 88
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr PhysicalDeviceMeshShaderPropertiesNV -> IO b -> IO b
pokeZeroCStruct p :: Ptr PhysicalDeviceMeshShaderPropertiesNV
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMeshShaderPropertiesNV
p Ptr PhysicalDeviceMeshShaderPropertiesNV
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_MESH_SHADER_PROPERTIES_NV)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMeshShaderPropertiesNV
p Ptr PhysicalDeviceMeshShaderPropertiesNV -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr ("taskCount" ::: Word32) -> ("taskCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMeshShaderPropertiesNV
p Ptr PhysicalDeviceMeshShaderPropertiesNV
-> Int -> Ptr ("taskCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32)) ("taskCount" ::: Word32
forall a. Zero a => a
zero)
    Ptr ("taskCount" ::: Word32) -> ("taskCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMeshShaderPropertiesNV
p Ptr PhysicalDeviceMeshShaderPropertiesNV
-> Int -> Ptr ("taskCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32)) ("taskCount" ::: Word32
forall a. Zero a => a
zero)
    let pMaxTaskWorkGroupSize' :: Ptr ("taskCount" ::: Word32)
pMaxTaskWorkGroupSize' = Ptr (FixedArray 3 ("taskCount" ::: Word32))
-> Ptr ("taskCount" ::: Word32)
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr ((Ptr PhysicalDeviceMeshShaderPropertiesNV
p Ptr PhysicalDeviceMeshShaderPropertiesNV
-> Int -> Ptr (FixedArray 3 ("taskCount" ::: Word32))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (FixedArray 3 Word32)))
    case (("taskCount" ::: Word32
forall a. Zero a => a
zero, "taskCount" ::: Word32
forall a. Zero a => a
zero, "taskCount" ::: Word32
forall a. Zero a => a
zero)) of
      (e0 :: "taskCount" ::: Word32
e0, e1 :: "taskCount" ::: Word32
e1, e2 :: "taskCount" ::: Word32
e2) -> do
        Ptr ("taskCount" ::: Word32) -> ("taskCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ("taskCount" ::: Word32)
pMaxTaskWorkGroupSize' :: Ptr Word32) ("taskCount" ::: Word32
e0)
        Ptr ("taskCount" ::: Word32) -> ("taskCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ("taskCount" ::: Word32)
pMaxTaskWorkGroupSize' Ptr ("taskCount" ::: Word32) -> Int -> Ptr ("taskCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32) ("taskCount" ::: Word32
e1)
        Ptr ("taskCount" ::: Word32) -> ("taskCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ("taskCount" ::: Word32)
pMaxTaskWorkGroupSize' Ptr ("taskCount" ::: Word32) -> Int -> Ptr ("taskCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Word32) ("taskCount" ::: Word32
e2)
    Ptr ("taskCount" ::: Word32) -> ("taskCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMeshShaderPropertiesNV
p Ptr PhysicalDeviceMeshShaderPropertiesNV
-> Int -> Ptr ("taskCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 36 :: Ptr Word32)) ("taskCount" ::: Word32
forall a. Zero a => a
zero)
    Ptr ("taskCount" ::: Word32) -> ("taskCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMeshShaderPropertiesNV
p Ptr PhysicalDeviceMeshShaderPropertiesNV
-> Int -> Ptr ("taskCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr Word32)) ("taskCount" ::: Word32
forall a. Zero a => a
zero)
    Ptr ("taskCount" ::: Word32) -> ("taskCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMeshShaderPropertiesNV
p Ptr PhysicalDeviceMeshShaderPropertiesNV
-> Int -> Ptr ("taskCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 44 :: Ptr Word32)) ("taskCount" ::: Word32
forall a. Zero a => a
zero)
    let pMaxMeshWorkGroupSize' :: Ptr ("taskCount" ::: Word32)
pMaxMeshWorkGroupSize' = Ptr (FixedArray 3 ("taskCount" ::: Word32))
-> Ptr ("taskCount" ::: Word32)
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr ((Ptr PhysicalDeviceMeshShaderPropertiesNV
p Ptr PhysicalDeviceMeshShaderPropertiesNV
-> Int -> Ptr (FixedArray 3 ("taskCount" ::: Word32))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr (FixedArray 3 Word32)))
    case (("taskCount" ::: Word32
forall a. Zero a => a
zero, "taskCount" ::: Word32
forall a. Zero a => a
zero, "taskCount" ::: Word32
forall a. Zero a => a
zero)) of
      (e0 :: "taskCount" ::: Word32
e0, e1 :: "taskCount" ::: Word32
e1, e2 :: "taskCount" ::: Word32
e2) -> do
        Ptr ("taskCount" ::: Word32) -> ("taskCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ("taskCount" ::: Word32)
pMaxMeshWorkGroupSize' :: Ptr Word32) ("taskCount" ::: Word32
e0)
        Ptr ("taskCount" ::: Word32) -> ("taskCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ("taskCount" ::: Word32)
pMaxMeshWorkGroupSize' Ptr ("taskCount" ::: Word32) -> Int -> Ptr ("taskCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32) ("taskCount" ::: Word32
e1)
        Ptr ("taskCount" ::: Word32) -> ("taskCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ("taskCount" ::: Word32)
pMaxMeshWorkGroupSize' Ptr ("taskCount" ::: Word32) -> Int -> Ptr ("taskCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Word32) ("taskCount" ::: Word32
e2)
    Ptr ("taskCount" ::: Word32) -> ("taskCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMeshShaderPropertiesNV
p Ptr PhysicalDeviceMeshShaderPropertiesNV
-> Int -> Ptr ("taskCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 60 :: Ptr Word32)) ("taskCount" ::: Word32
forall a. Zero a => a
zero)
    Ptr ("taskCount" ::: Word32) -> ("taskCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMeshShaderPropertiesNV
p Ptr PhysicalDeviceMeshShaderPropertiesNV
-> Int -> Ptr ("taskCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64 :: Ptr Word32)) ("taskCount" ::: Word32
forall a. Zero a => a
zero)
    Ptr ("taskCount" ::: Word32) -> ("taskCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMeshShaderPropertiesNV
p Ptr PhysicalDeviceMeshShaderPropertiesNV
-> Int -> Ptr ("taskCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 68 :: Ptr Word32)) ("taskCount" ::: Word32
forall a. Zero a => a
zero)
    Ptr ("taskCount" ::: Word32) -> ("taskCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMeshShaderPropertiesNV
p Ptr PhysicalDeviceMeshShaderPropertiesNV
-> Int -> Ptr ("taskCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 72 :: Ptr Word32)) ("taskCount" ::: Word32
forall a. Zero a => a
zero)
    Ptr ("taskCount" ::: Word32) -> ("taskCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMeshShaderPropertiesNV
p Ptr PhysicalDeviceMeshShaderPropertiesNV
-> Int -> Ptr ("taskCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 76 :: Ptr Word32)) ("taskCount" ::: Word32
forall a. Zero a => a
zero)
    Ptr ("taskCount" ::: Word32) -> ("taskCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMeshShaderPropertiesNV
p Ptr PhysicalDeviceMeshShaderPropertiesNV
-> Int -> Ptr ("taskCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 80 :: Ptr Word32)) ("taskCount" ::: Word32
forall a. Zero a => a
zero)
    IO b
f
instance FromCStruct PhysicalDeviceMeshShaderPropertiesNV where
  peekCStruct :: Ptr PhysicalDeviceMeshShaderPropertiesNV
-> IO PhysicalDeviceMeshShaderPropertiesNV
peekCStruct p :: Ptr PhysicalDeviceMeshShaderPropertiesNV
p = do
    "taskCount" ::: Word32
maxDrawMeshTasksCount <- Ptr ("taskCount" ::: Word32) -> IO ("taskCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceMeshShaderPropertiesNV
p Ptr PhysicalDeviceMeshShaderPropertiesNV
-> Int -> Ptr ("taskCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32))
    "taskCount" ::: Word32
maxTaskWorkGroupInvocations <- Ptr ("taskCount" ::: Word32) -> IO ("taskCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceMeshShaderPropertiesNV
p Ptr PhysicalDeviceMeshShaderPropertiesNV
-> Int -> Ptr ("taskCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32))
    let pmaxTaskWorkGroupSize :: Ptr ("taskCount" ::: Word32)
pmaxTaskWorkGroupSize = Ptr (FixedArray 3 ("taskCount" ::: Word32))
-> Ptr ("taskCount" ::: Word32)
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr @Word32 ((Ptr PhysicalDeviceMeshShaderPropertiesNV
p Ptr PhysicalDeviceMeshShaderPropertiesNV
-> Int -> Ptr (FixedArray 3 ("taskCount" ::: Word32))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (FixedArray 3 Word32)))
    "taskCount" ::: Word32
maxTaskWorkGroupSize0 <- Ptr ("taskCount" ::: Word32) -> IO ("taskCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr ("taskCount" ::: Word32)
pmaxTaskWorkGroupSize Ptr ("taskCount" ::: Word32) -> Int -> Ptr ("taskCount" ::: Word32)
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` 0 :: Ptr Word32))
    "taskCount" ::: Word32
maxTaskWorkGroupSize1 <- Ptr ("taskCount" ::: Word32) -> IO ("taskCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr ("taskCount" ::: Word32)
pmaxTaskWorkGroupSize Ptr ("taskCount" ::: Word32) -> Int -> Ptr ("taskCount" ::: Word32)
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` 4 :: Ptr Word32))
    "taskCount" ::: Word32
maxTaskWorkGroupSize2 <- Ptr ("taskCount" ::: Word32) -> IO ("taskCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr ("taskCount" ::: Word32)
pmaxTaskWorkGroupSize Ptr ("taskCount" ::: Word32) -> Int -> Ptr ("taskCount" ::: Word32)
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` 8 :: Ptr Word32))
    "taskCount" ::: Word32
maxTaskTotalMemorySize <- Ptr ("taskCount" ::: Word32) -> IO ("taskCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceMeshShaderPropertiesNV
p Ptr PhysicalDeviceMeshShaderPropertiesNV
-> Int -> Ptr ("taskCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 36 :: Ptr Word32))
    "taskCount" ::: Word32
maxTaskOutputCount <- Ptr ("taskCount" ::: Word32) -> IO ("taskCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceMeshShaderPropertiesNV
p Ptr PhysicalDeviceMeshShaderPropertiesNV
-> Int -> Ptr ("taskCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr Word32))
    "taskCount" ::: Word32
maxMeshWorkGroupInvocations <- Ptr ("taskCount" ::: Word32) -> IO ("taskCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceMeshShaderPropertiesNV
p Ptr PhysicalDeviceMeshShaderPropertiesNV
-> Int -> Ptr ("taskCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 44 :: Ptr Word32))
    let pmaxMeshWorkGroupSize :: Ptr ("taskCount" ::: Word32)
pmaxMeshWorkGroupSize = Ptr (FixedArray 3 ("taskCount" ::: Word32))
-> Ptr ("taskCount" ::: Word32)
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr @Word32 ((Ptr PhysicalDeviceMeshShaderPropertiesNV
p Ptr PhysicalDeviceMeshShaderPropertiesNV
-> Int -> Ptr (FixedArray 3 ("taskCount" ::: Word32))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr (FixedArray 3 Word32)))
    "taskCount" ::: Word32
maxMeshWorkGroupSize0 <- Ptr ("taskCount" ::: Word32) -> IO ("taskCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr ("taskCount" ::: Word32)
pmaxMeshWorkGroupSize Ptr ("taskCount" ::: Word32) -> Int -> Ptr ("taskCount" ::: Word32)
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` 0 :: Ptr Word32))
    "taskCount" ::: Word32
maxMeshWorkGroupSize1 <- Ptr ("taskCount" ::: Word32) -> IO ("taskCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr ("taskCount" ::: Word32)
pmaxMeshWorkGroupSize Ptr ("taskCount" ::: Word32) -> Int -> Ptr ("taskCount" ::: Word32)
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` 4 :: Ptr Word32))
    "taskCount" ::: Word32
maxMeshWorkGroupSize2 <- Ptr ("taskCount" ::: Word32) -> IO ("taskCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr ("taskCount" ::: Word32)
pmaxMeshWorkGroupSize Ptr ("taskCount" ::: Word32) -> Int -> Ptr ("taskCount" ::: Word32)
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` 8 :: Ptr Word32))
    "taskCount" ::: Word32
maxMeshTotalMemorySize <- Ptr ("taskCount" ::: Word32) -> IO ("taskCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceMeshShaderPropertiesNV
p Ptr PhysicalDeviceMeshShaderPropertiesNV
-> Int -> Ptr ("taskCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 60 :: Ptr Word32))
    "taskCount" ::: Word32
maxMeshOutputVertices <- Ptr ("taskCount" ::: Word32) -> IO ("taskCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceMeshShaderPropertiesNV
p Ptr PhysicalDeviceMeshShaderPropertiesNV
-> Int -> Ptr ("taskCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64 :: Ptr Word32))
    "taskCount" ::: Word32
maxMeshOutputPrimitives <- Ptr ("taskCount" ::: Word32) -> IO ("taskCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceMeshShaderPropertiesNV
p Ptr PhysicalDeviceMeshShaderPropertiesNV
-> Int -> Ptr ("taskCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 68 :: Ptr Word32))
    "taskCount" ::: Word32
maxMeshMultiviewViewCount <- Ptr ("taskCount" ::: Word32) -> IO ("taskCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceMeshShaderPropertiesNV
p Ptr PhysicalDeviceMeshShaderPropertiesNV
-> Int -> Ptr ("taskCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 72 :: Ptr Word32))
    "taskCount" ::: Word32
meshOutputPerVertexGranularity <- Ptr ("taskCount" ::: Word32) -> IO ("taskCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceMeshShaderPropertiesNV
p Ptr PhysicalDeviceMeshShaderPropertiesNV
-> Int -> Ptr ("taskCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 76 :: Ptr Word32))
    "taskCount" ::: Word32
meshOutputPerPrimitiveGranularity <- Ptr ("taskCount" ::: Word32) -> IO ("taskCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceMeshShaderPropertiesNV
p Ptr PhysicalDeviceMeshShaderPropertiesNV
-> Int -> Ptr ("taskCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 80 :: Ptr Word32))
    PhysicalDeviceMeshShaderPropertiesNV
-> IO PhysicalDeviceMeshShaderPropertiesNV
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDeviceMeshShaderPropertiesNV
 -> IO PhysicalDeviceMeshShaderPropertiesNV)
-> PhysicalDeviceMeshShaderPropertiesNV
-> IO PhysicalDeviceMeshShaderPropertiesNV
forall a b. (a -> b) -> a -> b
$ ("taskCount" ::: Word32)
-> ("taskCount" ::: Word32)
-> ("taskCount" ::: Word32, "taskCount" ::: Word32,
    "taskCount" ::: Word32)
-> ("taskCount" ::: Word32)
-> ("taskCount" ::: Word32)
-> ("taskCount" ::: Word32)
-> ("taskCount" ::: Word32, "taskCount" ::: Word32,
    "taskCount" ::: Word32)
-> ("taskCount" ::: Word32)
-> ("taskCount" ::: Word32)
-> ("taskCount" ::: Word32)
-> ("taskCount" ::: Word32)
-> ("taskCount" ::: Word32)
-> ("taskCount" ::: Word32)
-> PhysicalDeviceMeshShaderPropertiesNV
PhysicalDeviceMeshShaderPropertiesNV
             "taskCount" ::: Word32
maxDrawMeshTasksCount "taskCount" ::: Word32
maxTaskWorkGroupInvocations (("taskCount" ::: Word32
maxTaskWorkGroupSize0, "taskCount" ::: Word32
maxTaskWorkGroupSize1, "taskCount" ::: Word32
maxTaskWorkGroupSize2)) "taskCount" ::: Word32
maxTaskTotalMemorySize "taskCount" ::: Word32
maxTaskOutputCount "taskCount" ::: Word32
maxMeshWorkGroupInvocations (("taskCount" ::: Word32
maxMeshWorkGroupSize0, "taskCount" ::: Word32
maxMeshWorkGroupSize1, "taskCount" ::: Word32
maxMeshWorkGroupSize2)) "taskCount" ::: Word32
maxMeshTotalMemorySize "taskCount" ::: Word32
maxMeshOutputVertices "taskCount" ::: Word32
maxMeshOutputPrimitives "taskCount" ::: Word32
maxMeshMultiviewViewCount "taskCount" ::: Word32
meshOutputPerVertexGranularity "taskCount" ::: Word32
meshOutputPerPrimitiveGranularity
instance Storable PhysicalDeviceMeshShaderPropertiesNV where
  sizeOf :: PhysicalDeviceMeshShaderPropertiesNV -> Int
sizeOf ~PhysicalDeviceMeshShaderPropertiesNV
_ = 88
  alignment :: PhysicalDeviceMeshShaderPropertiesNV -> Int
alignment ~PhysicalDeviceMeshShaderPropertiesNV
_ = 8
  peek :: Ptr PhysicalDeviceMeshShaderPropertiesNV
-> IO PhysicalDeviceMeshShaderPropertiesNV
peek = Ptr PhysicalDeviceMeshShaderPropertiesNV
-> IO PhysicalDeviceMeshShaderPropertiesNV
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: Ptr PhysicalDeviceMeshShaderPropertiesNV
-> PhysicalDeviceMeshShaderPropertiesNV -> IO ()
poke ptr :: Ptr PhysicalDeviceMeshShaderPropertiesNV
ptr poked :: PhysicalDeviceMeshShaderPropertiesNV
poked = Ptr PhysicalDeviceMeshShaderPropertiesNV
-> PhysicalDeviceMeshShaderPropertiesNV -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceMeshShaderPropertiesNV
ptr PhysicalDeviceMeshShaderPropertiesNV
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PhysicalDeviceMeshShaderPropertiesNV where
  zero :: PhysicalDeviceMeshShaderPropertiesNV
zero = ("taskCount" ::: Word32)
-> ("taskCount" ::: Word32)
-> ("taskCount" ::: Word32, "taskCount" ::: Word32,
    "taskCount" ::: Word32)
-> ("taskCount" ::: Word32)
-> ("taskCount" ::: Word32)
-> ("taskCount" ::: Word32)
-> ("taskCount" ::: Word32, "taskCount" ::: Word32,
    "taskCount" ::: Word32)
-> ("taskCount" ::: Word32)
-> ("taskCount" ::: Word32)
-> ("taskCount" ::: Word32)
-> ("taskCount" ::: Word32)
-> ("taskCount" ::: Word32)
-> ("taskCount" ::: Word32)
-> PhysicalDeviceMeshShaderPropertiesNV
PhysicalDeviceMeshShaderPropertiesNV
           "taskCount" ::: Word32
forall a. Zero a => a
zero
           "taskCount" ::: Word32
forall a. Zero a => a
zero
           ("taskCount" ::: Word32
forall a. Zero a => a
zero, "taskCount" ::: Word32
forall a. Zero a => a
zero, "taskCount" ::: Word32
forall a. Zero a => a
zero)
           "taskCount" ::: Word32
forall a. Zero a => a
zero
           "taskCount" ::: Word32
forall a. Zero a => a
zero
           "taskCount" ::: Word32
forall a. Zero a => a
zero
           ("taskCount" ::: Word32
forall a. Zero a => a
zero, "taskCount" ::: Word32
forall a. Zero a => a
zero, "taskCount" ::: Word32
forall a. Zero a => a
zero)
           "taskCount" ::: Word32
forall a. Zero a => a
zero
           "taskCount" ::: Word32
forall a. Zero a => a
zero
           "taskCount" ::: Word32
forall a. Zero a => a
zero
           "taskCount" ::: Word32
forall a. Zero a => a
zero
           "taskCount" ::: Word32
forall a. Zero a => a
zero
           "taskCount" ::: Word32
forall a. Zero a => a
zero
data DrawMeshTasksIndirectCommandNV = DrawMeshTasksIndirectCommandNV
  { 
    
    
    
    
    DrawMeshTasksIndirectCommandNV -> "taskCount" ::: Word32
taskCount :: Word32
  , 
    DrawMeshTasksIndirectCommandNV -> "taskCount" ::: Word32
firstTask :: Word32
  }
  deriving (Typeable, DrawMeshTasksIndirectCommandNV
-> DrawMeshTasksIndirectCommandNV -> Bool
(DrawMeshTasksIndirectCommandNV
 -> DrawMeshTasksIndirectCommandNV -> Bool)
-> (DrawMeshTasksIndirectCommandNV
    -> DrawMeshTasksIndirectCommandNV -> Bool)
-> Eq DrawMeshTasksIndirectCommandNV
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DrawMeshTasksIndirectCommandNV
-> DrawMeshTasksIndirectCommandNV -> Bool
$c/= :: DrawMeshTasksIndirectCommandNV
-> DrawMeshTasksIndirectCommandNV -> Bool
== :: DrawMeshTasksIndirectCommandNV
-> DrawMeshTasksIndirectCommandNV -> Bool
$c== :: DrawMeshTasksIndirectCommandNV
-> DrawMeshTasksIndirectCommandNV -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (DrawMeshTasksIndirectCommandNV)
#endif
deriving instance Show DrawMeshTasksIndirectCommandNV
instance ToCStruct DrawMeshTasksIndirectCommandNV where
  withCStruct :: DrawMeshTasksIndirectCommandNV
-> (Ptr DrawMeshTasksIndirectCommandNV -> IO b) -> IO b
withCStruct x :: DrawMeshTasksIndirectCommandNV
x f :: Ptr DrawMeshTasksIndirectCommandNV -> IO b
f = Int -> Int -> (Ptr DrawMeshTasksIndirectCommandNV -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 8 4 ((Ptr DrawMeshTasksIndirectCommandNV -> IO b) -> IO b)
-> (Ptr DrawMeshTasksIndirectCommandNV -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr DrawMeshTasksIndirectCommandNV
p -> Ptr DrawMeshTasksIndirectCommandNV
-> DrawMeshTasksIndirectCommandNV -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr DrawMeshTasksIndirectCommandNV
p DrawMeshTasksIndirectCommandNV
x (Ptr DrawMeshTasksIndirectCommandNV -> IO b
f Ptr DrawMeshTasksIndirectCommandNV
p)
  pokeCStruct :: Ptr DrawMeshTasksIndirectCommandNV
-> DrawMeshTasksIndirectCommandNV -> IO b -> IO b
pokeCStruct p :: Ptr DrawMeshTasksIndirectCommandNV
p DrawMeshTasksIndirectCommandNV{..} f :: IO b
f = do
    Ptr ("taskCount" ::: Word32) -> ("taskCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DrawMeshTasksIndirectCommandNV
p Ptr DrawMeshTasksIndirectCommandNV
-> Int -> Ptr ("taskCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Word32)) ("taskCount" ::: Word32
taskCount)
    Ptr ("taskCount" ::: Word32) -> ("taskCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DrawMeshTasksIndirectCommandNV
p Ptr DrawMeshTasksIndirectCommandNV
-> Int -> Ptr ("taskCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32)) ("taskCount" ::: Word32
firstTask)
    IO b
f
  cStructSize :: Int
cStructSize = 8
  cStructAlignment :: Int
cStructAlignment = 4
  pokeZeroCStruct :: Ptr DrawMeshTasksIndirectCommandNV -> IO b -> IO b
pokeZeroCStruct p :: Ptr DrawMeshTasksIndirectCommandNV
p f :: IO b
f = do
    Ptr ("taskCount" ::: Word32) -> ("taskCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DrawMeshTasksIndirectCommandNV
p Ptr DrawMeshTasksIndirectCommandNV
-> Int -> Ptr ("taskCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Word32)) ("taskCount" ::: Word32
forall a. Zero a => a
zero)
    Ptr ("taskCount" ::: Word32) -> ("taskCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DrawMeshTasksIndirectCommandNV
p Ptr DrawMeshTasksIndirectCommandNV
-> Int -> Ptr ("taskCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32)) ("taskCount" ::: Word32
forall a. Zero a => a
zero)
    IO b
f
instance FromCStruct DrawMeshTasksIndirectCommandNV where
  peekCStruct :: Ptr DrawMeshTasksIndirectCommandNV
-> IO DrawMeshTasksIndirectCommandNV
peekCStruct p :: Ptr DrawMeshTasksIndirectCommandNV
p = do
    "taskCount" ::: Word32
taskCount <- Ptr ("taskCount" ::: Word32) -> IO ("taskCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr DrawMeshTasksIndirectCommandNV
p Ptr DrawMeshTasksIndirectCommandNV
-> Int -> Ptr ("taskCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Word32))
    "taskCount" ::: Word32
firstTask <- Ptr ("taskCount" ::: Word32) -> IO ("taskCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr DrawMeshTasksIndirectCommandNV
p Ptr DrawMeshTasksIndirectCommandNV
-> Int -> Ptr ("taskCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32))
    DrawMeshTasksIndirectCommandNV -> IO DrawMeshTasksIndirectCommandNV
forall (f :: * -> *) a. Applicative f => a -> f a
pure (DrawMeshTasksIndirectCommandNV
 -> IO DrawMeshTasksIndirectCommandNV)
-> DrawMeshTasksIndirectCommandNV
-> IO DrawMeshTasksIndirectCommandNV
forall a b. (a -> b) -> a -> b
$ ("taskCount" ::: Word32)
-> ("taskCount" ::: Word32) -> DrawMeshTasksIndirectCommandNV
DrawMeshTasksIndirectCommandNV
             "taskCount" ::: Word32
taskCount "taskCount" ::: Word32
firstTask
instance Storable DrawMeshTasksIndirectCommandNV where
  sizeOf :: DrawMeshTasksIndirectCommandNV -> Int
sizeOf ~DrawMeshTasksIndirectCommandNV
_ = 8
  alignment :: DrawMeshTasksIndirectCommandNV -> Int
alignment ~DrawMeshTasksIndirectCommandNV
_ = 4
  peek :: Ptr DrawMeshTasksIndirectCommandNV
-> IO DrawMeshTasksIndirectCommandNV
peek = Ptr DrawMeshTasksIndirectCommandNV
-> IO DrawMeshTasksIndirectCommandNV
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: Ptr DrawMeshTasksIndirectCommandNV
-> DrawMeshTasksIndirectCommandNV -> IO ()
poke ptr :: Ptr DrawMeshTasksIndirectCommandNV
ptr poked :: DrawMeshTasksIndirectCommandNV
poked = Ptr DrawMeshTasksIndirectCommandNV
-> DrawMeshTasksIndirectCommandNV -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr DrawMeshTasksIndirectCommandNV
ptr DrawMeshTasksIndirectCommandNV
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero DrawMeshTasksIndirectCommandNV where
  zero :: DrawMeshTasksIndirectCommandNV
zero = ("taskCount" ::: Word32)
-> ("taskCount" ::: Word32) -> DrawMeshTasksIndirectCommandNV
DrawMeshTasksIndirectCommandNV
           "taskCount" ::: Word32
forall a. Zero a => a
zero
           "taskCount" ::: Word32
forall a. Zero a => a
zero
type NV_MESH_SHADER_SPEC_VERSION = 1
pattern NV_MESH_SHADER_SPEC_VERSION :: forall a . Integral a => a
pattern $bNV_MESH_SHADER_SPEC_VERSION :: a
$mNV_MESH_SHADER_SPEC_VERSION :: forall r a. Integral a => a -> (Void# -> r) -> (Void# -> r) -> r
NV_MESH_SHADER_SPEC_VERSION = 1
type NV_MESH_SHADER_EXTENSION_NAME = "VK_NV_mesh_shader"
pattern NV_MESH_SHADER_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bNV_MESH_SHADER_EXTENSION_NAME :: a
$mNV_MESH_SHADER_EXTENSION_NAME :: forall r a.
(Eq a, IsString a) =>
a -> (Void# -> r) -> (Void# -> r) -> r
NV_MESH_SHADER_EXTENSION_NAME = "VK_NV_mesh_shader"