{-# language CPP #-}
module Vulkan.Extensions.VK_EXT_subgroup_size_control  ( PhysicalDeviceSubgroupSizeControlFeaturesEXT(..)
                                                       , PhysicalDeviceSubgroupSizeControlPropertiesEXT(..)
                                                       , PipelineShaderStageRequiredSubgroupSizeCreateInfoEXT(..)
                                                       , EXT_SUBGROUP_SIZE_CONTROL_SPEC_VERSION
                                                       , pattern EXT_SUBGROUP_SIZE_CONTROL_SPEC_VERSION
                                                       , EXT_SUBGROUP_SIZE_CONTROL_EXTENSION_NAME
                                                       , pattern EXT_SUBGROUP_SIZE_CONTROL_EXTENSION_NAME
                                                       ) where

import Foreign.Marshal.Alloc (allocaBytesAligned)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
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 Foreign.Ptr (Ptr)
import Data.Word (Word32)
import Data.Kind (Type)
import Vulkan.Core10.FundamentalTypes (bool32ToBool)
import Vulkan.Core10.FundamentalTypes (boolToBool32)
import Vulkan.Core10.FundamentalTypes (Bool32)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.Core10.Enums.ShaderStageFlagBits (ShaderStageFlags)
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_SUBGROUP_SIZE_CONTROL_FEATURES_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_SUBGROUP_SIZE_CONTROL_PROPERTIES_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PIPELINE_SHADER_STAGE_REQUIRED_SUBGROUP_SIZE_CREATE_INFO_EXT))
-- | VkPhysicalDeviceSubgroupSizeControlFeaturesEXT - Structure describing
-- the subgroup size control features that can be supported by an
-- implementation
--
-- = Members
--
-- The members of the 'PhysicalDeviceSubgroupSizeControlFeaturesEXT'
-- structure describe the following features:
--
-- = Description
--
-- If the 'PhysicalDeviceSubgroupSizeControlFeaturesEXT' 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.
-- 'PhysicalDeviceSubgroupSizeControlFeaturesEXT' /can/ also be included in
-- the @pNext@ chain of 'Vulkan.Core10.Device.DeviceCreateInfo' to enable
-- the feature.
--
-- Note
--
-- The 'PhysicalDeviceSubgroupSizeControlFeaturesEXT' structure was added
-- in version 2 of the @VK_EXT_subgroup_size_control@ extension. Version 1
-- implementations of this extension will not fill out the features
-- structure but applications may assume that both @subgroupSizeControl@
-- and @computeFullSubgroups@ are supported if the extension is supported.
-- (See also the
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-requirements Feature Requirements>
-- section.) Applications are advised to add a
-- 'PhysicalDeviceSubgroupSizeControlFeaturesEXT' structure to the @pNext@
-- chain of 'Vulkan.Core10.Device.DeviceCreateInfo' to enable the features
-- regardless of the version of the extension supported by the
-- implementation. If the implementation only supports version 1, it will
-- safely ignore the 'PhysicalDeviceSubgroupSizeControlFeaturesEXT'
-- structure.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDeviceSubgroupSizeControlFeaturesEXT = PhysicalDeviceSubgroupSizeControlFeaturesEXT
  { -- | @subgroupSizeControl@ indicates whether the implementation supports
    -- controlling shader subgroup sizes via the
    -- 'Vulkan.Core10.Enums.PipelineShaderStageCreateFlagBits.PIPELINE_SHADER_STAGE_CREATE_ALLOW_VARYING_SUBGROUP_SIZE_BIT_EXT'
    -- flag and the 'PipelineShaderStageRequiredSubgroupSizeCreateInfoEXT'
    -- structure.
    PhysicalDeviceSubgroupSizeControlFeaturesEXT -> Bool
subgroupSizeControl :: Bool
  , -- | @computeFullSubgroups@ indicates whether the implementation supports
    -- requiring full subgroups in compute shaders via the
    -- 'Vulkan.Core10.Enums.PipelineShaderStageCreateFlagBits.PIPELINE_SHADER_STAGE_CREATE_REQUIRE_FULL_SUBGROUPS_BIT_EXT'
    -- flag.
    PhysicalDeviceSubgroupSizeControlFeaturesEXT -> Bool
computeFullSubgroups :: Bool
  }
  deriving (Typeable, PhysicalDeviceSubgroupSizeControlFeaturesEXT
-> PhysicalDeviceSubgroupSizeControlFeaturesEXT -> Bool
(PhysicalDeviceSubgroupSizeControlFeaturesEXT
 -> PhysicalDeviceSubgroupSizeControlFeaturesEXT -> Bool)
-> (PhysicalDeviceSubgroupSizeControlFeaturesEXT
    -> PhysicalDeviceSubgroupSizeControlFeaturesEXT -> Bool)
-> Eq PhysicalDeviceSubgroupSizeControlFeaturesEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceSubgroupSizeControlFeaturesEXT
-> PhysicalDeviceSubgroupSizeControlFeaturesEXT -> Bool
$c/= :: PhysicalDeviceSubgroupSizeControlFeaturesEXT
-> PhysicalDeviceSubgroupSizeControlFeaturesEXT -> Bool
== :: PhysicalDeviceSubgroupSizeControlFeaturesEXT
-> PhysicalDeviceSubgroupSizeControlFeaturesEXT -> Bool
$c== :: PhysicalDeviceSubgroupSizeControlFeaturesEXT
-> PhysicalDeviceSubgroupSizeControlFeaturesEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceSubgroupSizeControlFeaturesEXT)
#endif
deriving instance Show PhysicalDeviceSubgroupSizeControlFeaturesEXT

instance ToCStruct PhysicalDeviceSubgroupSizeControlFeaturesEXT where
  withCStruct :: PhysicalDeviceSubgroupSizeControlFeaturesEXT
-> (Ptr PhysicalDeviceSubgroupSizeControlFeaturesEXT -> IO b)
-> IO b
withCStruct x :: PhysicalDeviceSubgroupSizeControlFeaturesEXT
x f :: Ptr PhysicalDeviceSubgroupSizeControlFeaturesEXT -> IO b
f = Int
-> Int
-> (Ptr PhysicalDeviceSubgroupSizeControlFeaturesEXT -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 8 ((Ptr PhysicalDeviceSubgroupSizeControlFeaturesEXT -> IO b)
 -> IO b)
-> (Ptr PhysicalDeviceSubgroupSizeControlFeaturesEXT -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr PhysicalDeviceSubgroupSizeControlFeaturesEXT
p -> Ptr PhysicalDeviceSubgroupSizeControlFeaturesEXT
-> PhysicalDeviceSubgroupSizeControlFeaturesEXT -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceSubgroupSizeControlFeaturesEXT
p PhysicalDeviceSubgroupSizeControlFeaturesEXT
x (Ptr PhysicalDeviceSubgroupSizeControlFeaturesEXT -> IO b
f Ptr PhysicalDeviceSubgroupSizeControlFeaturesEXT
p)
  pokeCStruct :: Ptr PhysicalDeviceSubgroupSizeControlFeaturesEXT
-> PhysicalDeviceSubgroupSizeControlFeaturesEXT -> IO b -> IO b
pokeCStruct p :: Ptr PhysicalDeviceSubgroupSizeControlFeaturesEXT
p PhysicalDeviceSubgroupSizeControlFeaturesEXT{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceSubgroupSizeControlFeaturesEXT
p Ptr PhysicalDeviceSubgroupSizeControlFeaturesEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_SUBGROUP_SIZE_CONTROL_FEATURES_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceSubgroupSizeControlFeaturesEXT
p Ptr PhysicalDeviceSubgroupSizeControlFeaturesEXT
-> 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 PhysicalDeviceSubgroupSizeControlFeaturesEXT
p Ptr PhysicalDeviceSubgroupSizeControlFeaturesEXT
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
subgroupSizeControl))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceSubgroupSizeControlFeaturesEXT
p Ptr PhysicalDeviceSubgroupSizeControlFeaturesEXT
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
computeFullSubgroups))
    IO b
f
  cStructSize :: Int
cStructSize = 24
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr PhysicalDeviceSubgroupSizeControlFeaturesEXT -> IO b -> IO b
pokeZeroCStruct p :: Ptr PhysicalDeviceSubgroupSizeControlFeaturesEXT
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceSubgroupSizeControlFeaturesEXT
p Ptr PhysicalDeviceSubgroupSizeControlFeaturesEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_SUBGROUP_SIZE_CONTROL_FEATURES_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceSubgroupSizeControlFeaturesEXT
p Ptr PhysicalDeviceSubgroupSizeControlFeaturesEXT
-> 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 PhysicalDeviceSubgroupSizeControlFeaturesEXT
p Ptr PhysicalDeviceSubgroupSizeControlFeaturesEXT
-> 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 PhysicalDeviceSubgroupSizeControlFeaturesEXT
p Ptr PhysicalDeviceSubgroupSizeControlFeaturesEXT
-> 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 PhysicalDeviceSubgroupSizeControlFeaturesEXT where
  peekCStruct :: Ptr PhysicalDeviceSubgroupSizeControlFeaturesEXT
-> IO PhysicalDeviceSubgroupSizeControlFeaturesEXT
peekCStruct p :: Ptr PhysicalDeviceSubgroupSizeControlFeaturesEXT
p = do
    Bool32
subgroupSizeControl <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceSubgroupSizeControlFeaturesEXT
p Ptr PhysicalDeviceSubgroupSizeControlFeaturesEXT
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32))
    Bool32
computeFullSubgroups <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceSubgroupSizeControlFeaturesEXT
p Ptr PhysicalDeviceSubgroupSizeControlFeaturesEXT
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Bool32))
    PhysicalDeviceSubgroupSizeControlFeaturesEXT
-> IO PhysicalDeviceSubgroupSizeControlFeaturesEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDeviceSubgroupSizeControlFeaturesEXT
 -> IO PhysicalDeviceSubgroupSizeControlFeaturesEXT)
-> PhysicalDeviceSubgroupSizeControlFeaturesEXT
-> IO PhysicalDeviceSubgroupSizeControlFeaturesEXT
forall a b. (a -> b) -> a -> b
$ Bool -> Bool -> PhysicalDeviceSubgroupSizeControlFeaturesEXT
PhysicalDeviceSubgroupSizeControlFeaturesEXT
             (Bool32 -> Bool
bool32ToBool Bool32
subgroupSizeControl) (Bool32 -> Bool
bool32ToBool Bool32
computeFullSubgroups)

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

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


-- | VkPhysicalDeviceSubgroupSizeControlPropertiesEXT - Structure describing
-- the control subgroup size properties of an implementation
--
-- = Members
--
-- The members of the 'PhysicalDeviceSubgroupSizeControlPropertiesEXT'
-- structure describe the following properties:
--
-- = Description
--
-- If the 'PhysicalDeviceSubgroupSizeControlPropertiesEXT' 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.
--
-- If
-- 'Vulkan.Core11.Originally_Based_On_VK_KHR_subgroup.PhysicalDeviceSubgroupProperties'::@supportedOperations@
-- includes
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-subgroup-quad >,
-- @minSubgroupSize@ /must/ be greater than or equal to 4.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'Vulkan.Core10.Enums.ShaderStageFlagBits.ShaderStageFlags',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDeviceSubgroupSizeControlPropertiesEXT = PhysicalDeviceSubgroupSizeControlPropertiesEXT
  { -- | @minSubgroupSize@ is the minimum subgroup size supported by this device.
    -- @minSubgroupSize@ is at least one if any of the physical device’s queues
    -- support 'Vulkan.Core10.Enums.QueueFlagBits.QUEUE_GRAPHICS_BIT' or
    -- 'Vulkan.Core10.Enums.QueueFlagBits.QUEUE_COMPUTE_BIT'. @minSubgroupSize@
    -- is a power-of-two. @minSubgroupSize@ is less than or equal to
    -- @maxSubgroupSize@. @minSubgroupSize@ is less than or equal to
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-subgroup-size subgroupSize>.
    PhysicalDeviceSubgroupSizeControlPropertiesEXT -> Word32
minSubgroupSize :: Word32
  , -- | @maxSubgroupSize@ is the maximum subgroup size supported by this device.
    -- @maxSubgroupSize@ is at least one if any of the physical device’s queues
    -- support 'Vulkan.Core10.Enums.QueueFlagBits.QUEUE_GRAPHICS_BIT' or
    -- 'Vulkan.Core10.Enums.QueueFlagBits.QUEUE_COMPUTE_BIT'. @maxSubgroupSize@
    -- is a power-of-two. @maxSubgroupSize@ is greater than or equal to
    -- @minSubgroupSize@. @maxSubgroupSize@ is greater than or equal to
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-subgroup-size subgroupSize>.
    PhysicalDeviceSubgroupSizeControlPropertiesEXT -> Word32
maxSubgroupSize :: Word32
  , -- | @maxComputeWorkgroupSubgroups@ is the maximum number of subgroups
    -- supported by the implementation within a workgroup.
    PhysicalDeviceSubgroupSizeControlPropertiesEXT -> Word32
maxComputeWorkgroupSubgroups :: Word32
  , -- | @requiredSubgroupSizeStages@ is a bitfield of what shader stages support
    -- having a required subgroup size specified.
    PhysicalDeviceSubgroupSizeControlPropertiesEXT -> ShaderStageFlags
requiredSubgroupSizeStages :: ShaderStageFlags
  }
  deriving (Typeable, PhysicalDeviceSubgroupSizeControlPropertiesEXT
-> PhysicalDeviceSubgroupSizeControlPropertiesEXT -> Bool
(PhysicalDeviceSubgroupSizeControlPropertiesEXT
 -> PhysicalDeviceSubgroupSizeControlPropertiesEXT -> Bool)
-> (PhysicalDeviceSubgroupSizeControlPropertiesEXT
    -> PhysicalDeviceSubgroupSizeControlPropertiesEXT -> Bool)
-> Eq PhysicalDeviceSubgroupSizeControlPropertiesEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceSubgroupSizeControlPropertiesEXT
-> PhysicalDeviceSubgroupSizeControlPropertiesEXT -> Bool
$c/= :: PhysicalDeviceSubgroupSizeControlPropertiesEXT
-> PhysicalDeviceSubgroupSizeControlPropertiesEXT -> Bool
== :: PhysicalDeviceSubgroupSizeControlPropertiesEXT
-> PhysicalDeviceSubgroupSizeControlPropertiesEXT -> Bool
$c== :: PhysicalDeviceSubgroupSizeControlPropertiesEXT
-> PhysicalDeviceSubgroupSizeControlPropertiesEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceSubgroupSizeControlPropertiesEXT)
#endif
deriving instance Show PhysicalDeviceSubgroupSizeControlPropertiesEXT

instance ToCStruct PhysicalDeviceSubgroupSizeControlPropertiesEXT where
  withCStruct :: PhysicalDeviceSubgroupSizeControlPropertiesEXT
-> (Ptr PhysicalDeviceSubgroupSizeControlPropertiesEXT -> IO b)
-> IO b
withCStruct x :: PhysicalDeviceSubgroupSizeControlPropertiesEXT
x f :: Ptr PhysicalDeviceSubgroupSizeControlPropertiesEXT -> IO b
f = Int
-> Int
-> (Ptr PhysicalDeviceSubgroupSizeControlPropertiesEXT -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 32 8 ((Ptr PhysicalDeviceSubgroupSizeControlPropertiesEXT -> IO b)
 -> IO b)
-> (Ptr PhysicalDeviceSubgroupSizeControlPropertiesEXT -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr PhysicalDeviceSubgroupSizeControlPropertiesEXT
p -> Ptr PhysicalDeviceSubgroupSizeControlPropertiesEXT
-> PhysicalDeviceSubgroupSizeControlPropertiesEXT -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceSubgroupSizeControlPropertiesEXT
p PhysicalDeviceSubgroupSizeControlPropertiesEXT
x (Ptr PhysicalDeviceSubgroupSizeControlPropertiesEXT -> IO b
f Ptr PhysicalDeviceSubgroupSizeControlPropertiesEXT
p)
  pokeCStruct :: Ptr PhysicalDeviceSubgroupSizeControlPropertiesEXT
-> PhysicalDeviceSubgroupSizeControlPropertiesEXT -> IO b -> IO b
pokeCStruct p :: Ptr PhysicalDeviceSubgroupSizeControlPropertiesEXT
p PhysicalDeviceSubgroupSizeControlPropertiesEXT{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceSubgroupSizeControlPropertiesEXT
p Ptr PhysicalDeviceSubgroupSizeControlPropertiesEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_SUBGROUP_SIZE_CONTROL_PROPERTIES_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceSubgroupSizeControlPropertiesEXT
p Ptr PhysicalDeviceSubgroupSizeControlPropertiesEXT
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceSubgroupSizeControlPropertiesEXT
p Ptr PhysicalDeviceSubgroupSizeControlPropertiesEXT
-> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32)) (Word32
minSubgroupSize)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceSubgroupSizeControlPropertiesEXT
p Ptr PhysicalDeviceSubgroupSizeControlPropertiesEXT
-> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32)) (Word32
maxSubgroupSize)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceSubgroupSizeControlPropertiesEXT
p Ptr PhysicalDeviceSubgroupSizeControlPropertiesEXT
-> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Word32)) (Word32
maxComputeWorkgroupSubgroups)
    Ptr ShaderStageFlags -> ShaderStageFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceSubgroupSizeControlPropertiesEXT
p Ptr PhysicalDeviceSubgroupSizeControlPropertiesEXT
-> Int -> Ptr ShaderStageFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr ShaderStageFlags)) (ShaderStageFlags
requiredSubgroupSizeStages)
    IO b
f
  cStructSize :: Int
cStructSize = 32
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr PhysicalDeviceSubgroupSizeControlPropertiesEXT -> IO b -> IO b
pokeZeroCStruct p :: Ptr PhysicalDeviceSubgroupSizeControlPropertiesEXT
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceSubgroupSizeControlPropertiesEXT
p Ptr PhysicalDeviceSubgroupSizeControlPropertiesEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_SUBGROUP_SIZE_CONTROL_PROPERTIES_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceSubgroupSizeControlPropertiesEXT
p Ptr PhysicalDeviceSubgroupSizeControlPropertiesEXT
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceSubgroupSizeControlPropertiesEXT
p Ptr PhysicalDeviceSubgroupSizeControlPropertiesEXT
-> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceSubgroupSizeControlPropertiesEXT
p Ptr PhysicalDeviceSubgroupSizeControlPropertiesEXT
-> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceSubgroupSizeControlPropertiesEXT
p Ptr PhysicalDeviceSubgroupSizeControlPropertiesEXT
-> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr ShaderStageFlags -> ShaderStageFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceSubgroupSizeControlPropertiesEXT
p Ptr PhysicalDeviceSubgroupSizeControlPropertiesEXT
-> Int -> Ptr ShaderStageFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr ShaderStageFlags)) (ShaderStageFlags
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct PhysicalDeviceSubgroupSizeControlPropertiesEXT where
  peekCStruct :: Ptr PhysicalDeviceSubgroupSizeControlPropertiesEXT
-> IO PhysicalDeviceSubgroupSizeControlPropertiesEXT
peekCStruct p :: Ptr PhysicalDeviceSubgroupSizeControlPropertiesEXT
p = do
    Word32
minSubgroupSize <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceSubgroupSizeControlPropertiesEXT
p Ptr PhysicalDeviceSubgroupSizeControlPropertiesEXT
-> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32))
    Word32
maxSubgroupSize <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceSubgroupSizeControlPropertiesEXT
p Ptr PhysicalDeviceSubgroupSizeControlPropertiesEXT
-> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32))
    Word32
maxComputeWorkgroupSubgroups <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceSubgroupSizeControlPropertiesEXT
p Ptr PhysicalDeviceSubgroupSizeControlPropertiesEXT
-> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Word32))
    ShaderStageFlags
requiredSubgroupSizeStages <- Ptr ShaderStageFlags -> IO ShaderStageFlags
forall a. Storable a => Ptr a -> IO a
peek @ShaderStageFlags ((Ptr PhysicalDeviceSubgroupSizeControlPropertiesEXT
p Ptr PhysicalDeviceSubgroupSizeControlPropertiesEXT
-> Int -> Ptr ShaderStageFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr ShaderStageFlags))
    PhysicalDeviceSubgroupSizeControlPropertiesEXT
-> IO PhysicalDeviceSubgroupSizeControlPropertiesEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDeviceSubgroupSizeControlPropertiesEXT
 -> IO PhysicalDeviceSubgroupSizeControlPropertiesEXT)
-> PhysicalDeviceSubgroupSizeControlPropertiesEXT
-> IO PhysicalDeviceSubgroupSizeControlPropertiesEXT
forall a b. (a -> b) -> a -> b
$ Word32
-> Word32
-> Word32
-> ShaderStageFlags
-> PhysicalDeviceSubgroupSizeControlPropertiesEXT
PhysicalDeviceSubgroupSizeControlPropertiesEXT
             Word32
minSubgroupSize Word32
maxSubgroupSize Word32
maxComputeWorkgroupSubgroups ShaderStageFlags
requiredSubgroupSizeStages

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

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


-- | VkPipelineShaderStageRequiredSubgroupSizeCreateInfoEXT - Structure
-- specifying the required subgroup size of a newly created pipeline shader
-- stage
--
-- == Valid Usage
--
-- = Description
--
-- If a 'PipelineShaderStageRequiredSubgroupSizeCreateInfoEXT' structure is
-- included in the @pNext@ chain of
-- 'Vulkan.Core10.Pipeline.PipelineShaderStageCreateInfo', it specifies
-- that the pipeline shader stage being compiled has a required subgroup
-- size.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PipelineShaderStageRequiredSubgroupSizeCreateInfoEXT = PipelineShaderStageRequiredSubgroupSizeCreateInfoEXT
  { -- | @requiredSubgroupSize@ /must/ be a power-of-two integer
    --
    -- @requiredSubgroupSize@ /must/ be greater or equal to
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-min-subgroup-size minSubgroupSize>
    --
    -- @requiredSubgroupSize@ /must/ be less than or equal to
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-max-subgroup-size maxSubgroupSize>
    PipelineShaderStageRequiredSubgroupSizeCreateInfoEXT -> Word32
requiredSubgroupSize :: Word32 }
  deriving (Typeable, PipelineShaderStageRequiredSubgroupSizeCreateInfoEXT
-> PipelineShaderStageRequiredSubgroupSizeCreateInfoEXT -> Bool
(PipelineShaderStageRequiredSubgroupSizeCreateInfoEXT
 -> PipelineShaderStageRequiredSubgroupSizeCreateInfoEXT -> Bool)
-> (PipelineShaderStageRequiredSubgroupSizeCreateInfoEXT
    -> PipelineShaderStageRequiredSubgroupSizeCreateInfoEXT -> Bool)
-> Eq PipelineShaderStageRequiredSubgroupSizeCreateInfoEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PipelineShaderStageRequiredSubgroupSizeCreateInfoEXT
-> PipelineShaderStageRequiredSubgroupSizeCreateInfoEXT -> Bool
$c/= :: PipelineShaderStageRequiredSubgroupSizeCreateInfoEXT
-> PipelineShaderStageRequiredSubgroupSizeCreateInfoEXT -> Bool
== :: PipelineShaderStageRequiredSubgroupSizeCreateInfoEXT
-> PipelineShaderStageRequiredSubgroupSizeCreateInfoEXT -> Bool
$c== :: PipelineShaderStageRequiredSubgroupSizeCreateInfoEXT
-> PipelineShaderStageRequiredSubgroupSizeCreateInfoEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PipelineShaderStageRequiredSubgroupSizeCreateInfoEXT)
#endif
deriving instance Show PipelineShaderStageRequiredSubgroupSizeCreateInfoEXT

instance ToCStruct PipelineShaderStageRequiredSubgroupSizeCreateInfoEXT where
  withCStruct :: PipelineShaderStageRequiredSubgroupSizeCreateInfoEXT
-> (Ptr PipelineShaderStageRequiredSubgroupSizeCreateInfoEXT
    -> IO b)
-> IO b
withCStruct x :: PipelineShaderStageRequiredSubgroupSizeCreateInfoEXT
x f :: Ptr PipelineShaderStageRequiredSubgroupSizeCreateInfoEXT -> IO b
f = Int
-> Int
-> (Ptr PipelineShaderStageRequiredSubgroupSizeCreateInfoEXT
    -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 8 ((Ptr PipelineShaderStageRequiredSubgroupSizeCreateInfoEXT -> IO b)
 -> IO b)
-> (Ptr PipelineShaderStageRequiredSubgroupSizeCreateInfoEXT
    -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr PipelineShaderStageRequiredSubgroupSizeCreateInfoEXT
p -> Ptr PipelineShaderStageRequiredSubgroupSizeCreateInfoEXT
-> PipelineShaderStageRequiredSubgroupSizeCreateInfoEXT
-> IO b
-> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PipelineShaderStageRequiredSubgroupSizeCreateInfoEXT
p PipelineShaderStageRequiredSubgroupSizeCreateInfoEXT
x (Ptr PipelineShaderStageRequiredSubgroupSizeCreateInfoEXT -> IO b
f Ptr PipelineShaderStageRequiredSubgroupSizeCreateInfoEXT
p)
  pokeCStruct :: Ptr PipelineShaderStageRequiredSubgroupSizeCreateInfoEXT
-> PipelineShaderStageRequiredSubgroupSizeCreateInfoEXT
-> IO b
-> IO b
pokeCStruct p :: Ptr PipelineShaderStageRequiredSubgroupSizeCreateInfoEXT
p PipelineShaderStageRequiredSubgroupSizeCreateInfoEXT{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineShaderStageRequiredSubgroupSizeCreateInfoEXT
p Ptr PipelineShaderStageRequiredSubgroupSizeCreateInfoEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PIPELINE_SHADER_STAGE_REQUIRED_SUBGROUP_SIZE_CREATE_INFO_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineShaderStageRequiredSubgroupSizeCreateInfoEXT
p Ptr PipelineShaderStageRequiredSubgroupSizeCreateInfoEXT
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineShaderStageRequiredSubgroupSizeCreateInfoEXT
p Ptr PipelineShaderStageRequiredSubgroupSizeCreateInfoEXT
-> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32)) (Word32
requiredSubgroupSize)
    IO b
f
  cStructSize :: Int
cStructSize = 24
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr PipelineShaderStageRequiredSubgroupSizeCreateInfoEXT
-> IO b -> IO b
pokeZeroCStruct p :: Ptr PipelineShaderStageRequiredSubgroupSizeCreateInfoEXT
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineShaderStageRequiredSubgroupSizeCreateInfoEXT
p Ptr PipelineShaderStageRequiredSubgroupSizeCreateInfoEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PIPELINE_SHADER_STAGE_REQUIRED_SUBGROUP_SIZE_CREATE_INFO_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineShaderStageRequiredSubgroupSizeCreateInfoEXT
p Ptr PipelineShaderStageRequiredSubgroupSizeCreateInfoEXT
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineShaderStageRequiredSubgroupSizeCreateInfoEXT
p Ptr PipelineShaderStageRequiredSubgroupSizeCreateInfoEXT
-> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    IO b
f

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

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

instance Zero PipelineShaderStageRequiredSubgroupSizeCreateInfoEXT where
  zero :: PipelineShaderStageRequiredSubgroupSizeCreateInfoEXT
zero = Word32 -> PipelineShaderStageRequiredSubgroupSizeCreateInfoEXT
PipelineShaderStageRequiredSubgroupSizeCreateInfoEXT
           Word32
forall a. Zero a => a
zero


type EXT_SUBGROUP_SIZE_CONTROL_SPEC_VERSION = 2

-- No documentation found for TopLevel "VK_EXT_SUBGROUP_SIZE_CONTROL_SPEC_VERSION"
pattern EXT_SUBGROUP_SIZE_CONTROL_SPEC_VERSION :: forall a . Integral a => a
pattern $bEXT_SUBGROUP_SIZE_CONTROL_SPEC_VERSION :: a
$mEXT_SUBGROUP_SIZE_CONTROL_SPEC_VERSION :: forall r a. Integral a => a -> (Void# -> r) -> (Void# -> r) -> r
EXT_SUBGROUP_SIZE_CONTROL_SPEC_VERSION = 2


type EXT_SUBGROUP_SIZE_CONTROL_EXTENSION_NAME = "VK_EXT_subgroup_size_control"

-- No documentation found for TopLevel "VK_EXT_SUBGROUP_SIZE_CONTROL_EXTENSION_NAME"
pattern EXT_SUBGROUP_SIZE_CONTROL_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bEXT_SUBGROUP_SIZE_CONTROL_EXTENSION_NAME :: a
$mEXT_SUBGROUP_SIZE_CONTROL_EXTENSION_NAME :: forall r a.
(Eq a, IsString a) =>
a -> (Void# -> r) -> (Void# -> r) -> r
EXT_SUBGROUP_SIZE_CONTROL_EXTENSION_NAME = "VK_EXT_subgroup_size_control"