{-# language CPP #-}
module Vulkan.Core13 ( pattern API_VERSION_1_3
, PhysicalDeviceVulkan13Features(..)
, PhysicalDeviceVulkan13Properties(..)
, StructureType(..)
, Flags64
, module Vulkan.Core13.Enums
, module Vulkan.Core13.Handles
, module Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state
, module Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2
, module Vulkan.Core13.Promoted_From_VK_EXT_image_robustness
, module Vulkan.Core13.Promoted_From_VK_EXT_inline_uniform_block
, module Vulkan.Core13.Promoted_From_VK_EXT_pipeline_creation_cache_control
, module Vulkan.Core13.Promoted_From_VK_EXT_pipeline_creation_feedback
, module Vulkan.Core13.Promoted_From_VK_EXT_private_data
, module Vulkan.Core13.Promoted_From_VK_EXT_shader_demote_to_helper_invocation
, module Vulkan.Core13.Promoted_From_VK_EXT_subgroup_size_control
, module Vulkan.Core13.Promoted_From_VK_EXT_texel_buffer_alignment
, module Vulkan.Core13.Promoted_From_VK_EXT_texture_compression_astc_hdr
, module Vulkan.Core13.Promoted_From_VK_EXT_tooling_info
, module Vulkan.Core13.Promoted_From_VK_KHR_copy_commands2
, module Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering
, module Vulkan.Core13.Promoted_From_VK_KHR_format_feature_flags2
, module Vulkan.Core13.Promoted_From_VK_KHR_maintenance4
, module Vulkan.Core13.Promoted_From_VK_KHR_shader_integer_dot_product
, module Vulkan.Core13.Promoted_From_VK_KHR_shader_terminate_invocation
, module Vulkan.Core13.Promoted_From_VK_KHR_synchronization2
, module Vulkan.Core13.Promoted_From_VK_KHR_zero_initialize_workgroup_memory
) where
import Vulkan.Core13.Enums
import Vulkan.Core13.Handles
import Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state
import Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state2
import Vulkan.Core13.Promoted_From_VK_EXT_image_robustness
import Vulkan.Core13.Promoted_From_VK_EXT_inline_uniform_block
import Vulkan.Core13.Promoted_From_VK_EXT_pipeline_creation_cache_control
import Vulkan.Core13.Promoted_From_VK_EXT_pipeline_creation_feedback
import Vulkan.Core13.Promoted_From_VK_EXT_private_data
import Vulkan.Core13.Promoted_From_VK_EXT_shader_demote_to_helper_invocation
import Vulkan.Core13.Promoted_From_VK_EXT_subgroup_size_control
import Vulkan.Core13.Promoted_From_VK_EXT_texel_buffer_alignment
import Vulkan.Core13.Promoted_From_VK_EXT_texture_compression_astc_hdr
import Vulkan.Core13.Promoted_From_VK_EXT_tooling_info
import Vulkan.Core13.Promoted_From_VK_KHR_copy_commands2
import Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering
import Vulkan.Core13.Promoted_From_VK_KHR_format_feature_flags2
import Vulkan.Core13.Promoted_From_VK_KHR_maintenance4
import Vulkan.Core13.Promoted_From_VK_KHR_shader_integer_dot_product
import Vulkan.Core13.Promoted_From_VK_KHR_shader_terminate_invocation
import Vulkan.Core13.Promoted_From_VK_KHR_synchronization2
import Vulkan.Core13.Promoted_From_VK_KHR_zero_initialize_workgroup_memory
import Foreign.Marshal.Alloc (allocaBytes)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Zero (Zero(..))
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.Core10.FundamentalTypes (DeviceSize)
import Vulkan.Core10.Enums.ShaderStageFlagBits (ShaderStageFlags)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Version (pattern MAKE_API_VERSION)
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_VULKAN_1_3_FEATURES))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_VULKAN_1_3_PROPERTIES))
import Vulkan.Core10.FundamentalTypes (Flags64)
import Vulkan.Core10.Enums.StructureType (StructureType(..))
pattern API_VERSION_1_3 :: Word32
pattern $bAPI_VERSION_1_3 :: Word32
$mAPI_VERSION_1_3 :: forall {r}. Word32 -> ((# #) -> r) -> ((# #) -> r) -> r
API_VERSION_1_3 = MAKE_API_VERSION 1 3 0
data PhysicalDeviceVulkan13Features = PhysicalDeviceVulkan13Features
{
PhysicalDeviceVulkan13Features -> Bool
robustImageAccess :: Bool
,
PhysicalDeviceVulkan13Features -> Bool
inlineUniformBlock :: Bool
,
PhysicalDeviceVulkan13Features -> Bool
descriptorBindingInlineUniformBlockUpdateAfterBind :: Bool
,
PhysicalDeviceVulkan13Features -> Bool
pipelineCreationCacheControl :: Bool
,
PhysicalDeviceVulkan13Features -> Bool
privateData :: Bool
,
PhysicalDeviceVulkan13Features -> Bool
shaderDemoteToHelperInvocation :: Bool
,
PhysicalDeviceVulkan13Features -> Bool
shaderTerminateInvocation :: Bool
,
PhysicalDeviceVulkan13Features -> Bool
subgroupSizeControl :: Bool
,
PhysicalDeviceVulkan13Features -> Bool
computeFullSubgroups :: Bool
,
PhysicalDeviceVulkan13Features -> Bool
synchronization2 :: Bool
,
PhysicalDeviceVulkan13Features -> Bool
textureCompressionASTC_HDR :: Bool
,
PhysicalDeviceVulkan13Features -> Bool
shaderZeroInitializeWorkgroupMemory :: Bool
,
PhysicalDeviceVulkan13Features -> Bool
dynamicRendering :: Bool
,
PhysicalDeviceVulkan13Features -> Bool
shaderIntegerDotProduct :: Bool
,
PhysicalDeviceVulkan13Features -> Bool
maintenance4 :: Bool
}
deriving (Typeable, PhysicalDeviceVulkan13Features
-> PhysicalDeviceVulkan13Features -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceVulkan13Features
-> PhysicalDeviceVulkan13Features -> Bool
$c/= :: PhysicalDeviceVulkan13Features
-> PhysicalDeviceVulkan13Features -> Bool
== :: PhysicalDeviceVulkan13Features
-> PhysicalDeviceVulkan13Features -> Bool
$c== :: PhysicalDeviceVulkan13Features
-> PhysicalDeviceVulkan13Features -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceVulkan13Features)
#endif
deriving instance Show PhysicalDeviceVulkan13Features
instance ToCStruct PhysicalDeviceVulkan13Features where
withCStruct :: forall b.
PhysicalDeviceVulkan13Features
-> (Ptr PhysicalDeviceVulkan13Features -> IO b) -> IO b
withCStruct PhysicalDeviceVulkan13Features
x Ptr PhysicalDeviceVulkan13Features -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
80 forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceVulkan13Features
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceVulkan13Features
p PhysicalDeviceVulkan13Features
x (Ptr PhysicalDeviceVulkan13Features -> IO b
f Ptr PhysicalDeviceVulkan13Features
p)
pokeCStruct :: forall b.
Ptr PhysicalDeviceVulkan13Features
-> PhysicalDeviceVulkan13Features -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceVulkan13Features
p PhysicalDeviceVulkan13Features{Bool
maintenance4 :: Bool
shaderIntegerDotProduct :: Bool
dynamicRendering :: Bool
shaderZeroInitializeWorkgroupMemory :: Bool
textureCompressionASTC_HDR :: Bool
synchronization2 :: Bool
computeFullSubgroups :: Bool
subgroupSizeControl :: Bool
shaderTerminateInvocation :: Bool
shaderDemoteToHelperInvocation :: Bool
privateData :: Bool
pipelineCreationCacheControl :: Bool
descriptorBindingInlineUniformBlockUpdateAfterBind :: Bool
inlineUniformBlock :: Bool
robustImageAccess :: Bool
$sel:maintenance4:PhysicalDeviceVulkan13Features :: PhysicalDeviceVulkan13Features -> Bool
$sel:shaderIntegerDotProduct:PhysicalDeviceVulkan13Features :: PhysicalDeviceVulkan13Features -> Bool
$sel:dynamicRendering:PhysicalDeviceVulkan13Features :: PhysicalDeviceVulkan13Features -> Bool
$sel:shaderZeroInitializeWorkgroupMemory:PhysicalDeviceVulkan13Features :: PhysicalDeviceVulkan13Features -> Bool
$sel:textureCompressionASTC_HDR:PhysicalDeviceVulkan13Features :: PhysicalDeviceVulkan13Features -> Bool
$sel:synchronization2:PhysicalDeviceVulkan13Features :: PhysicalDeviceVulkan13Features -> Bool
$sel:computeFullSubgroups:PhysicalDeviceVulkan13Features :: PhysicalDeviceVulkan13Features -> Bool
$sel:subgroupSizeControl:PhysicalDeviceVulkan13Features :: PhysicalDeviceVulkan13Features -> Bool
$sel:shaderTerminateInvocation:PhysicalDeviceVulkan13Features :: PhysicalDeviceVulkan13Features -> Bool
$sel:shaderDemoteToHelperInvocation:PhysicalDeviceVulkan13Features :: PhysicalDeviceVulkan13Features -> Bool
$sel:privateData:PhysicalDeviceVulkan13Features :: PhysicalDeviceVulkan13Features -> Bool
$sel:pipelineCreationCacheControl:PhysicalDeviceVulkan13Features :: PhysicalDeviceVulkan13Features -> Bool
$sel:descriptorBindingInlineUniformBlockUpdateAfterBind:PhysicalDeviceVulkan13Features :: PhysicalDeviceVulkan13Features -> Bool
$sel:inlineUniformBlock:PhysicalDeviceVulkan13Features :: PhysicalDeviceVulkan13Features -> Bool
$sel:robustImageAccess:PhysicalDeviceVulkan13Features :: PhysicalDeviceVulkan13Features -> Bool
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_VULKAN_1_3_FEATURES)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
robustImageAccess))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
inlineUniformBlock))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
descriptorBindingInlineUniformBlockUpdateAfterBind))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
pipelineCreationCacheControl))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
privateData))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
36 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderDemoteToHelperInvocation))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderTerminateInvocation))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
44 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
subgroupSizeControl))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
computeFullSubgroups))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
52 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
synchronization2))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
textureCompressionASTC_HDR))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
60 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderZeroInitializeWorkgroupMemory))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
64 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
dynamicRendering))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
68 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderIntegerDotProduct))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
72 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
maintenance4))
IO b
f
cStructSize :: Int
cStructSize = Int
80
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b. Ptr PhysicalDeviceVulkan13Features -> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceVulkan13Features
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_VULKAN_1_3_FEATURES)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
36 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
44 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
52 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
60 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
64 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
68 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
72 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
IO b
f
instance FromCStruct PhysicalDeviceVulkan13Features where
peekCStruct :: Ptr PhysicalDeviceVulkan13Features
-> IO PhysicalDeviceVulkan13Features
peekCStruct Ptr PhysicalDeviceVulkan13Features
p = do
Bool32
robustImageAccess <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan13Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32))
Bool32
inlineUniformBlock <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan13Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32))
Bool32
descriptorBindingInlineUniformBlockUpdateAfterBind <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan13Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Bool32))
Bool32
pipelineCreationCacheControl <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan13Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr Bool32))
Bool32
privateData <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan13Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr Bool32))
Bool32
shaderDemoteToHelperInvocation <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan13Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
36 :: Ptr Bool32))
Bool32
shaderTerminateInvocation <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan13Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr Bool32))
Bool32
subgroupSizeControl <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan13Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
44 :: Ptr Bool32))
Bool32
computeFullSubgroups <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan13Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48 :: Ptr Bool32))
Bool32
synchronization2 <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan13Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
52 :: Ptr Bool32))
Bool32
textureCompressionASTC_HDR <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan13Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56 :: Ptr Bool32))
Bool32
shaderZeroInitializeWorkgroupMemory <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan13Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
60 :: Ptr Bool32))
Bool32
dynamicRendering <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan13Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
64 :: Ptr Bool32))
Bool32
shaderIntegerDotProduct <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan13Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
68 :: Ptr Bool32))
Bool32
maintenance4 <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan13Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
72 :: Ptr Bool32))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> PhysicalDeviceVulkan13Features
PhysicalDeviceVulkan13Features
(Bool32 -> Bool
bool32ToBool Bool32
robustImageAccess)
(Bool32 -> Bool
bool32ToBool Bool32
inlineUniformBlock)
(Bool32 -> Bool
bool32ToBool Bool32
descriptorBindingInlineUniformBlockUpdateAfterBind)
(Bool32 -> Bool
bool32ToBool Bool32
pipelineCreationCacheControl)
(Bool32 -> Bool
bool32ToBool Bool32
privateData)
(Bool32 -> Bool
bool32ToBool Bool32
shaderDemoteToHelperInvocation)
(Bool32 -> Bool
bool32ToBool Bool32
shaderTerminateInvocation)
(Bool32 -> Bool
bool32ToBool Bool32
subgroupSizeControl)
(Bool32 -> Bool
bool32ToBool Bool32
computeFullSubgroups)
(Bool32 -> Bool
bool32ToBool Bool32
synchronization2)
(Bool32 -> Bool
bool32ToBool Bool32
textureCompressionASTC_HDR)
(Bool32 -> Bool
bool32ToBool Bool32
shaderZeroInitializeWorkgroupMemory)
(Bool32 -> Bool
bool32ToBool Bool32
dynamicRendering)
(Bool32 -> Bool
bool32ToBool Bool32
shaderIntegerDotProduct)
(Bool32 -> Bool
bool32ToBool Bool32
maintenance4)
instance Storable PhysicalDeviceVulkan13Features where
sizeOf :: PhysicalDeviceVulkan13Features -> Int
sizeOf ~PhysicalDeviceVulkan13Features
_ = Int
80
alignment :: PhysicalDeviceVulkan13Features -> Int
alignment ~PhysicalDeviceVulkan13Features
_ = Int
8
peek :: Ptr PhysicalDeviceVulkan13Features
-> IO PhysicalDeviceVulkan13Features
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr PhysicalDeviceVulkan13Features
-> PhysicalDeviceVulkan13Features -> IO ()
poke Ptr PhysicalDeviceVulkan13Features
ptr PhysicalDeviceVulkan13Features
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceVulkan13Features
ptr PhysicalDeviceVulkan13Features
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PhysicalDeviceVulkan13Features where
zero :: PhysicalDeviceVulkan13Features
zero = Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> PhysicalDeviceVulkan13Features
PhysicalDeviceVulkan13Features
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
data PhysicalDeviceVulkan13Properties = PhysicalDeviceVulkan13Properties
{
PhysicalDeviceVulkan13Properties -> Word32
minSubgroupSize :: Word32
,
PhysicalDeviceVulkan13Properties -> Word32
maxSubgroupSize :: Word32
,
PhysicalDeviceVulkan13Properties -> Word32
maxComputeWorkgroupSubgroups :: Word32
,
PhysicalDeviceVulkan13Properties -> ShaderStageFlags
requiredSubgroupSizeStages :: ShaderStageFlags
,
PhysicalDeviceVulkan13Properties -> Word32
maxInlineUniformBlockSize :: Word32
,
PhysicalDeviceVulkan13Properties -> Word32
maxPerStageDescriptorInlineUniformBlocks :: Word32
,
PhysicalDeviceVulkan13Properties -> Word32
maxPerStageDescriptorUpdateAfterBindInlineUniformBlocks :: Word32
,
PhysicalDeviceVulkan13Properties -> Word32
maxDescriptorSetInlineUniformBlocks :: Word32
,
PhysicalDeviceVulkan13Properties -> Word32
maxDescriptorSetUpdateAfterBindInlineUniformBlocks :: Word32
,
PhysicalDeviceVulkan13Properties -> Word32
maxInlineUniformTotalSize :: Word32
,
PhysicalDeviceVulkan13Properties -> Bool
integerDotProduct8BitUnsignedAccelerated :: Bool
,
PhysicalDeviceVulkan13Properties -> Bool
integerDotProduct8BitSignedAccelerated :: Bool
,
PhysicalDeviceVulkan13Properties -> Bool
integerDotProduct8BitMixedSignednessAccelerated :: Bool
,
PhysicalDeviceVulkan13Properties -> Bool
integerDotProduct4x8BitPackedUnsignedAccelerated :: Bool
,
PhysicalDeviceVulkan13Properties -> Bool
integerDotProduct4x8BitPackedSignedAccelerated :: Bool
,
PhysicalDeviceVulkan13Properties -> Bool
integerDotProduct4x8BitPackedMixedSignednessAccelerated :: Bool
,
PhysicalDeviceVulkan13Properties -> Bool
integerDotProduct16BitUnsignedAccelerated :: Bool
,
PhysicalDeviceVulkan13Properties -> Bool
integerDotProduct16BitSignedAccelerated :: Bool
,
PhysicalDeviceVulkan13Properties -> Bool
integerDotProduct16BitMixedSignednessAccelerated :: Bool
,
PhysicalDeviceVulkan13Properties -> Bool
integerDotProduct32BitUnsignedAccelerated :: Bool
,
PhysicalDeviceVulkan13Properties -> Bool
integerDotProduct32BitSignedAccelerated :: Bool
,
PhysicalDeviceVulkan13Properties -> Bool
integerDotProduct32BitMixedSignednessAccelerated :: Bool
,
PhysicalDeviceVulkan13Properties -> Bool
integerDotProduct64BitUnsignedAccelerated :: Bool
,
PhysicalDeviceVulkan13Properties -> Bool
integerDotProduct64BitSignedAccelerated :: Bool
,
PhysicalDeviceVulkan13Properties -> Bool
integerDotProduct64BitMixedSignednessAccelerated :: Bool
,
PhysicalDeviceVulkan13Properties -> Bool
integerDotProductAccumulatingSaturating8BitUnsignedAccelerated :: Bool
,
PhysicalDeviceVulkan13Properties -> Bool
integerDotProductAccumulatingSaturating8BitSignedAccelerated :: Bool
,
PhysicalDeviceVulkan13Properties -> Bool
integerDotProductAccumulatingSaturating8BitMixedSignednessAccelerated :: Bool
,
PhysicalDeviceVulkan13Properties -> Bool
integerDotProductAccumulatingSaturating4x8BitPackedUnsignedAccelerated :: Bool
,
PhysicalDeviceVulkan13Properties -> Bool
integerDotProductAccumulatingSaturating4x8BitPackedSignedAccelerated :: Bool
,
PhysicalDeviceVulkan13Properties -> Bool
integerDotProductAccumulatingSaturating4x8BitPackedMixedSignednessAccelerated :: Bool
,
PhysicalDeviceVulkan13Properties -> Bool
integerDotProductAccumulatingSaturating16BitUnsignedAccelerated :: Bool
,
PhysicalDeviceVulkan13Properties -> Bool
integerDotProductAccumulatingSaturating16BitSignedAccelerated :: Bool
,
PhysicalDeviceVulkan13Properties -> Bool
integerDotProductAccumulatingSaturating16BitMixedSignednessAccelerated :: Bool
,
PhysicalDeviceVulkan13Properties -> Bool
integerDotProductAccumulatingSaturating32BitUnsignedAccelerated :: Bool
,
PhysicalDeviceVulkan13Properties -> Bool
integerDotProductAccumulatingSaturating32BitSignedAccelerated :: Bool
,
PhysicalDeviceVulkan13Properties -> Bool
integerDotProductAccumulatingSaturating32BitMixedSignednessAccelerated :: Bool
,
PhysicalDeviceVulkan13Properties -> Bool
integerDotProductAccumulatingSaturating64BitUnsignedAccelerated :: Bool
,
PhysicalDeviceVulkan13Properties -> Bool
integerDotProductAccumulatingSaturating64BitSignedAccelerated :: Bool
,
PhysicalDeviceVulkan13Properties -> Bool
integerDotProductAccumulatingSaturating64BitMixedSignednessAccelerated :: Bool
,
PhysicalDeviceVulkan13Properties -> DeviceSize
storageTexelBufferOffsetAlignmentBytes :: DeviceSize
,
PhysicalDeviceVulkan13Properties -> Bool
storageTexelBufferOffsetSingleTexelAlignment :: Bool
,
PhysicalDeviceVulkan13Properties -> DeviceSize
uniformTexelBufferOffsetAlignmentBytes :: DeviceSize
,
PhysicalDeviceVulkan13Properties -> Bool
uniformTexelBufferOffsetSingleTexelAlignment :: Bool
,
PhysicalDeviceVulkan13Properties -> DeviceSize
maxBufferSize :: DeviceSize
}
deriving (Typeable, PhysicalDeviceVulkan13Properties
-> PhysicalDeviceVulkan13Properties -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceVulkan13Properties
-> PhysicalDeviceVulkan13Properties -> Bool
$c/= :: PhysicalDeviceVulkan13Properties
-> PhysicalDeviceVulkan13Properties -> Bool
== :: PhysicalDeviceVulkan13Properties
-> PhysicalDeviceVulkan13Properties -> Bool
$c== :: PhysicalDeviceVulkan13Properties
-> PhysicalDeviceVulkan13Properties -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceVulkan13Properties)
#endif
deriving instance Show PhysicalDeviceVulkan13Properties
instance ToCStruct PhysicalDeviceVulkan13Properties where
withCStruct :: forall b.
PhysicalDeviceVulkan13Properties
-> (Ptr PhysicalDeviceVulkan13Properties -> IO b) -> IO b
withCStruct PhysicalDeviceVulkan13Properties
x Ptr PhysicalDeviceVulkan13Properties -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
216 forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceVulkan13Properties
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceVulkan13Properties
p PhysicalDeviceVulkan13Properties
x (Ptr PhysicalDeviceVulkan13Properties -> IO b
f Ptr PhysicalDeviceVulkan13Properties
p)
pokeCStruct :: forall b.
Ptr PhysicalDeviceVulkan13Properties
-> PhysicalDeviceVulkan13Properties -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceVulkan13Properties
p PhysicalDeviceVulkan13Properties{Bool
Word32
DeviceSize
ShaderStageFlags
maxBufferSize :: DeviceSize
uniformTexelBufferOffsetSingleTexelAlignment :: Bool
uniformTexelBufferOffsetAlignmentBytes :: DeviceSize
storageTexelBufferOffsetSingleTexelAlignment :: Bool
storageTexelBufferOffsetAlignmentBytes :: DeviceSize
integerDotProductAccumulatingSaturating64BitMixedSignednessAccelerated :: Bool
integerDotProductAccumulatingSaturating64BitSignedAccelerated :: Bool
integerDotProductAccumulatingSaturating64BitUnsignedAccelerated :: Bool
integerDotProductAccumulatingSaturating32BitMixedSignednessAccelerated :: Bool
integerDotProductAccumulatingSaturating32BitSignedAccelerated :: Bool
integerDotProductAccumulatingSaturating32BitUnsignedAccelerated :: Bool
integerDotProductAccumulatingSaturating16BitMixedSignednessAccelerated :: Bool
integerDotProductAccumulatingSaturating16BitSignedAccelerated :: Bool
integerDotProductAccumulatingSaturating16BitUnsignedAccelerated :: Bool
integerDotProductAccumulatingSaturating4x8BitPackedMixedSignednessAccelerated :: Bool
integerDotProductAccumulatingSaturating4x8BitPackedSignedAccelerated :: Bool
integerDotProductAccumulatingSaturating4x8BitPackedUnsignedAccelerated :: Bool
integerDotProductAccumulatingSaturating8BitMixedSignednessAccelerated :: Bool
integerDotProductAccumulatingSaturating8BitSignedAccelerated :: Bool
integerDotProductAccumulatingSaturating8BitUnsignedAccelerated :: Bool
integerDotProduct64BitMixedSignednessAccelerated :: Bool
integerDotProduct64BitSignedAccelerated :: Bool
integerDotProduct64BitUnsignedAccelerated :: Bool
integerDotProduct32BitMixedSignednessAccelerated :: Bool
integerDotProduct32BitSignedAccelerated :: Bool
integerDotProduct32BitUnsignedAccelerated :: Bool
integerDotProduct16BitMixedSignednessAccelerated :: Bool
integerDotProduct16BitSignedAccelerated :: Bool
integerDotProduct16BitUnsignedAccelerated :: Bool
integerDotProduct4x8BitPackedMixedSignednessAccelerated :: Bool
integerDotProduct4x8BitPackedSignedAccelerated :: Bool
integerDotProduct4x8BitPackedUnsignedAccelerated :: Bool
integerDotProduct8BitMixedSignednessAccelerated :: Bool
integerDotProduct8BitSignedAccelerated :: Bool
integerDotProduct8BitUnsignedAccelerated :: Bool
maxInlineUniformTotalSize :: Word32
maxDescriptorSetUpdateAfterBindInlineUniformBlocks :: Word32
maxDescriptorSetInlineUniformBlocks :: Word32
maxPerStageDescriptorUpdateAfterBindInlineUniformBlocks :: Word32
maxPerStageDescriptorInlineUniformBlocks :: Word32
maxInlineUniformBlockSize :: Word32
requiredSubgroupSizeStages :: ShaderStageFlags
maxComputeWorkgroupSubgroups :: Word32
maxSubgroupSize :: Word32
minSubgroupSize :: Word32
$sel:maxBufferSize:PhysicalDeviceVulkan13Properties :: PhysicalDeviceVulkan13Properties -> DeviceSize
$sel:uniformTexelBufferOffsetSingleTexelAlignment:PhysicalDeviceVulkan13Properties :: PhysicalDeviceVulkan13Properties -> Bool
$sel:uniformTexelBufferOffsetAlignmentBytes:PhysicalDeviceVulkan13Properties :: PhysicalDeviceVulkan13Properties -> DeviceSize
$sel:storageTexelBufferOffsetSingleTexelAlignment:PhysicalDeviceVulkan13Properties :: PhysicalDeviceVulkan13Properties -> Bool
$sel:storageTexelBufferOffsetAlignmentBytes:PhysicalDeviceVulkan13Properties :: PhysicalDeviceVulkan13Properties -> DeviceSize
$sel:integerDotProductAccumulatingSaturating64BitMixedSignednessAccelerated:PhysicalDeviceVulkan13Properties :: PhysicalDeviceVulkan13Properties -> Bool
$sel:integerDotProductAccumulatingSaturating64BitSignedAccelerated:PhysicalDeviceVulkan13Properties :: PhysicalDeviceVulkan13Properties -> Bool
$sel:integerDotProductAccumulatingSaturating64BitUnsignedAccelerated:PhysicalDeviceVulkan13Properties :: PhysicalDeviceVulkan13Properties -> Bool
$sel:integerDotProductAccumulatingSaturating32BitMixedSignednessAccelerated:PhysicalDeviceVulkan13Properties :: PhysicalDeviceVulkan13Properties -> Bool
$sel:integerDotProductAccumulatingSaturating32BitSignedAccelerated:PhysicalDeviceVulkan13Properties :: PhysicalDeviceVulkan13Properties -> Bool
$sel:integerDotProductAccumulatingSaturating32BitUnsignedAccelerated:PhysicalDeviceVulkan13Properties :: PhysicalDeviceVulkan13Properties -> Bool
$sel:integerDotProductAccumulatingSaturating16BitMixedSignednessAccelerated:PhysicalDeviceVulkan13Properties :: PhysicalDeviceVulkan13Properties -> Bool
$sel:integerDotProductAccumulatingSaturating16BitSignedAccelerated:PhysicalDeviceVulkan13Properties :: PhysicalDeviceVulkan13Properties -> Bool
$sel:integerDotProductAccumulatingSaturating16BitUnsignedAccelerated:PhysicalDeviceVulkan13Properties :: PhysicalDeviceVulkan13Properties -> Bool
$sel:integerDotProductAccumulatingSaturating4x8BitPackedMixedSignednessAccelerated:PhysicalDeviceVulkan13Properties :: PhysicalDeviceVulkan13Properties -> Bool
$sel:integerDotProductAccumulatingSaturating4x8BitPackedSignedAccelerated:PhysicalDeviceVulkan13Properties :: PhysicalDeviceVulkan13Properties -> Bool
$sel:integerDotProductAccumulatingSaturating4x8BitPackedUnsignedAccelerated:PhysicalDeviceVulkan13Properties :: PhysicalDeviceVulkan13Properties -> Bool
$sel:integerDotProductAccumulatingSaturating8BitMixedSignednessAccelerated:PhysicalDeviceVulkan13Properties :: PhysicalDeviceVulkan13Properties -> Bool
$sel:integerDotProductAccumulatingSaturating8BitSignedAccelerated:PhysicalDeviceVulkan13Properties :: PhysicalDeviceVulkan13Properties -> Bool
$sel:integerDotProductAccumulatingSaturating8BitUnsignedAccelerated:PhysicalDeviceVulkan13Properties :: PhysicalDeviceVulkan13Properties -> Bool
$sel:integerDotProduct64BitMixedSignednessAccelerated:PhysicalDeviceVulkan13Properties :: PhysicalDeviceVulkan13Properties -> Bool
$sel:integerDotProduct64BitSignedAccelerated:PhysicalDeviceVulkan13Properties :: PhysicalDeviceVulkan13Properties -> Bool
$sel:integerDotProduct64BitUnsignedAccelerated:PhysicalDeviceVulkan13Properties :: PhysicalDeviceVulkan13Properties -> Bool
$sel:integerDotProduct32BitMixedSignednessAccelerated:PhysicalDeviceVulkan13Properties :: PhysicalDeviceVulkan13Properties -> Bool
$sel:integerDotProduct32BitSignedAccelerated:PhysicalDeviceVulkan13Properties :: PhysicalDeviceVulkan13Properties -> Bool
$sel:integerDotProduct32BitUnsignedAccelerated:PhysicalDeviceVulkan13Properties :: PhysicalDeviceVulkan13Properties -> Bool
$sel:integerDotProduct16BitMixedSignednessAccelerated:PhysicalDeviceVulkan13Properties :: PhysicalDeviceVulkan13Properties -> Bool
$sel:integerDotProduct16BitSignedAccelerated:PhysicalDeviceVulkan13Properties :: PhysicalDeviceVulkan13Properties -> Bool
$sel:integerDotProduct16BitUnsignedAccelerated:PhysicalDeviceVulkan13Properties :: PhysicalDeviceVulkan13Properties -> Bool
$sel:integerDotProduct4x8BitPackedMixedSignednessAccelerated:PhysicalDeviceVulkan13Properties :: PhysicalDeviceVulkan13Properties -> Bool
$sel:integerDotProduct4x8BitPackedSignedAccelerated:PhysicalDeviceVulkan13Properties :: PhysicalDeviceVulkan13Properties -> Bool
$sel:integerDotProduct4x8BitPackedUnsignedAccelerated:PhysicalDeviceVulkan13Properties :: PhysicalDeviceVulkan13Properties -> Bool
$sel:integerDotProduct8BitMixedSignednessAccelerated:PhysicalDeviceVulkan13Properties :: PhysicalDeviceVulkan13Properties -> Bool
$sel:integerDotProduct8BitSignedAccelerated:PhysicalDeviceVulkan13Properties :: PhysicalDeviceVulkan13Properties -> Bool
$sel:integerDotProduct8BitUnsignedAccelerated:PhysicalDeviceVulkan13Properties :: PhysicalDeviceVulkan13Properties -> Bool
$sel:maxInlineUniformTotalSize:PhysicalDeviceVulkan13Properties :: PhysicalDeviceVulkan13Properties -> Word32
$sel:maxDescriptorSetUpdateAfterBindInlineUniformBlocks:PhysicalDeviceVulkan13Properties :: PhysicalDeviceVulkan13Properties -> Word32
$sel:maxDescriptorSetInlineUniformBlocks:PhysicalDeviceVulkan13Properties :: PhysicalDeviceVulkan13Properties -> Word32
$sel:maxPerStageDescriptorUpdateAfterBindInlineUniformBlocks:PhysicalDeviceVulkan13Properties :: PhysicalDeviceVulkan13Properties -> Word32
$sel:maxPerStageDescriptorInlineUniformBlocks:PhysicalDeviceVulkan13Properties :: PhysicalDeviceVulkan13Properties -> Word32
$sel:maxInlineUniformBlockSize:PhysicalDeviceVulkan13Properties :: PhysicalDeviceVulkan13Properties -> Word32
$sel:requiredSubgroupSizeStages:PhysicalDeviceVulkan13Properties :: PhysicalDeviceVulkan13Properties -> ShaderStageFlags
$sel:maxComputeWorkgroupSubgroups:PhysicalDeviceVulkan13Properties :: PhysicalDeviceVulkan13Properties -> Word32
$sel:maxSubgroupSize:PhysicalDeviceVulkan13Properties :: PhysicalDeviceVulkan13Properties -> Word32
$sel:minSubgroupSize:PhysicalDeviceVulkan13Properties :: PhysicalDeviceVulkan13Properties -> Word32
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_VULKAN_1_3_PROPERTIES)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32)) (Word32
minSubgroupSize)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Word32)) (Word32
maxSubgroupSize)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Word32)) (Word32
maxComputeWorkgroupSubgroups)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr ShaderStageFlags)) (ShaderStageFlags
requiredSubgroupSizeStages)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr Word32)) (Word32
maxInlineUniformBlockSize)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
36 :: Ptr Word32)) (Word32
maxPerStageDescriptorInlineUniformBlocks)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr Word32)) (Word32
maxPerStageDescriptorUpdateAfterBindInlineUniformBlocks)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
44 :: Ptr Word32)) (Word32
maxDescriptorSetInlineUniformBlocks)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48 :: Ptr Word32)) (Word32
maxDescriptorSetUpdateAfterBindInlineUniformBlocks)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
52 :: Ptr Word32)) (Word32
maxInlineUniformTotalSize)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
integerDotProduct8BitUnsignedAccelerated))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
60 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
integerDotProduct8BitSignedAccelerated))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
64 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
integerDotProduct8BitMixedSignednessAccelerated))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
68 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
integerDotProduct4x8BitPackedUnsignedAccelerated))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
72 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
integerDotProduct4x8BitPackedSignedAccelerated))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
76 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
integerDotProduct4x8BitPackedMixedSignednessAccelerated))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
80 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
integerDotProduct16BitUnsignedAccelerated))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
84 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
integerDotProduct16BitSignedAccelerated))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
88 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
integerDotProduct16BitMixedSignednessAccelerated))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
92 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
integerDotProduct32BitUnsignedAccelerated))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
96 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
integerDotProduct32BitSignedAccelerated))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
100 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
integerDotProduct32BitMixedSignednessAccelerated))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
104 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
integerDotProduct64BitUnsignedAccelerated))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
108 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
integerDotProduct64BitSignedAccelerated))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
112 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
integerDotProduct64BitMixedSignednessAccelerated))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
116 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
integerDotProductAccumulatingSaturating8BitUnsignedAccelerated))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
120 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
integerDotProductAccumulatingSaturating8BitSignedAccelerated))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
124 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
integerDotProductAccumulatingSaturating8BitMixedSignednessAccelerated))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
128 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
integerDotProductAccumulatingSaturating4x8BitPackedUnsignedAccelerated))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
132 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
integerDotProductAccumulatingSaturating4x8BitPackedSignedAccelerated))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
136 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
integerDotProductAccumulatingSaturating4x8BitPackedMixedSignednessAccelerated))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
140 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
integerDotProductAccumulatingSaturating16BitUnsignedAccelerated))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
144 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
integerDotProductAccumulatingSaturating16BitSignedAccelerated))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
148 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
integerDotProductAccumulatingSaturating16BitMixedSignednessAccelerated))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
152 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
integerDotProductAccumulatingSaturating32BitUnsignedAccelerated))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
156 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
integerDotProductAccumulatingSaturating32BitSignedAccelerated))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
160 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
integerDotProductAccumulatingSaturating32BitMixedSignednessAccelerated))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
164 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
integerDotProductAccumulatingSaturating64BitUnsignedAccelerated))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
168 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
integerDotProductAccumulatingSaturating64BitSignedAccelerated))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
172 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
integerDotProductAccumulatingSaturating64BitMixedSignednessAccelerated))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
176 :: Ptr DeviceSize)) (DeviceSize
storageTexelBufferOffsetAlignmentBytes)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
184 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
storageTexelBufferOffsetSingleTexelAlignment))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
192 :: Ptr DeviceSize)) (DeviceSize
uniformTexelBufferOffsetAlignmentBytes)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
200 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
uniformTexelBufferOffsetSingleTexelAlignment))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
208 :: Ptr DeviceSize)) (DeviceSize
maxBufferSize)
IO b
f
cStructSize :: Int
cStructSize = Int
216
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b. Ptr PhysicalDeviceVulkan13Properties -> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceVulkan13Properties
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_VULKAN_1_3_PROPERTIES)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Word32)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Word32)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr ShaderStageFlags)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr Word32)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
36 :: Ptr Word32)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr Word32)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
44 :: Ptr Word32)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48 :: Ptr Word32)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
52 :: Ptr Word32)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
60 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
64 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
68 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
72 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
76 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
80 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
84 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
88 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
92 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
96 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
100 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
104 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
108 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
112 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
116 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
120 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
124 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
128 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
132 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
136 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
140 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
144 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
148 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
152 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
156 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
160 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
164 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
168 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
172 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
176 :: Ptr DeviceSize)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
184 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
192 :: Ptr DeviceSize)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
200 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
208 :: Ptr DeviceSize)) (forall a. Zero a => a
zero)
IO b
f
instance FromCStruct PhysicalDeviceVulkan13Properties where
peekCStruct :: Ptr PhysicalDeviceVulkan13Properties
-> IO PhysicalDeviceVulkan13Properties
peekCStruct Ptr PhysicalDeviceVulkan13Properties
p = do
Word32
minSubgroupSize <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32))
Word32
maxSubgroupSize <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Word32))
Word32
maxComputeWorkgroupSubgroups <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Word32))
ShaderStageFlags
requiredSubgroupSizeStages <- forall a. Storable a => Ptr a -> IO a
peek @ShaderStageFlags ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr ShaderStageFlags))
Word32
maxInlineUniformBlockSize <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr Word32))
Word32
maxPerStageDescriptorInlineUniformBlocks <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
36 :: Ptr Word32))
Word32
maxPerStageDescriptorUpdateAfterBindInlineUniformBlocks <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr Word32))
Word32
maxDescriptorSetInlineUniformBlocks <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
44 :: Ptr Word32))
Word32
maxDescriptorSetUpdateAfterBindInlineUniformBlocks <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48 :: Ptr Word32))
Word32
maxInlineUniformTotalSize <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
52 :: Ptr Word32))
Bool32
integerDotProduct8BitUnsignedAccelerated <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56 :: Ptr Bool32))
Bool32
integerDotProduct8BitSignedAccelerated <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
60 :: Ptr Bool32))
Bool32
integerDotProduct8BitMixedSignednessAccelerated <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
64 :: Ptr Bool32))
Bool32
integerDotProduct4x8BitPackedUnsignedAccelerated <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
68 :: Ptr Bool32))
Bool32
integerDotProduct4x8BitPackedSignedAccelerated <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
72 :: Ptr Bool32))
Bool32
integerDotProduct4x8BitPackedMixedSignednessAccelerated <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
76 :: Ptr Bool32))
Bool32
integerDotProduct16BitUnsignedAccelerated <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
80 :: Ptr Bool32))
Bool32
integerDotProduct16BitSignedAccelerated <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
84 :: Ptr Bool32))
Bool32
integerDotProduct16BitMixedSignednessAccelerated <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
88 :: Ptr Bool32))
Bool32
integerDotProduct32BitUnsignedAccelerated <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
92 :: Ptr Bool32))
Bool32
integerDotProduct32BitSignedAccelerated <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
96 :: Ptr Bool32))
Bool32
integerDotProduct32BitMixedSignednessAccelerated <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
100 :: Ptr Bool32))
Bool32
integerDotProduct64BitUnsignedAccelerated <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
104 :: Ptr Bool32))
Bool32
integerDotProduct64BitSignedAccelerated <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
108 :: Ptr Bool32))
Bool32
integerDotProduct64BitMixedSignednessAccelerated <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
112 :: Ptr Bool32))
Bool32
integerDotProductAccumulatingSaturating8BitUnsignedAccelerated <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
116 :: Ptr Bool32))
Bool32
integerDotProductAccumulatingSaturating8BitSignedAccelerated <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
120 :: Ptr Bool32))
Bool32
integerDotProductAccumulatingSaturating8BitMixedSignednessAccelerated <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
124 :: Ptr Bool32))
Bool32
integerDotProductAccumulatingSaturating4x8BitPackedUnsignedAccelerated <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
128 :: Ptr Bool32))
Bool32
integerDotProductAccumulatingSaturating4x8BitPackedSignedAccelerated <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
132 :: Ptr Bool32))
Bool32
integerDotProductAccumulatingSaturating4x8BitPackedMixedSignednessAccelerated <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
136 :: Ptr Bool32))
Bool32
integerDotProductAccumulatingSaturating16BitUnsignedAccelerated <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
140 :: Ptr Bool32))
Bool32
integerDotProductAccumulatingSaturating16BitSignedAccelerated <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
144 :: Ptr Bool32))
Bool32
integerDotProductAccumulatingSaturating16BitMixedSignednessAccelerated <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
148 :: Ptr Bool32))
Bool32
integerDotProductAccumulatingSaturating32BitUnsignedAccelerated <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
152 :: Ptr Bool32))
Bool32
integerDotProductAccumulatingSaturating32BitSignedAccelerated <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
156 :: Ptr Bool32))
Bool32
integerDotProductAccumulatingSaturating32BitMixedSignednessAccelerated <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
160 :: Ptr Bool32))
Bool32
integerDotProductAccumulatingSaturating64BitUnsignedAccelerated <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
164 :: Ptr Bool32))
Bool32
integerDotProductAccumulatingSaturating64BitSignedAccelerated <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
168 :: Ptr Bool32))
Bool32
integerDotProductAccumulatingSaturating64BitMixedSignednessAccelerated <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
172 :: Ptr Bool32))
DeviceSize
storageTexelBufferOffsetAlignmentBytes <- forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
176 :: Ptr DeviceSize))
Bool32
storageTexelBufferOffsetSingleTexelAlignment <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
184 :: Ptr Bool32))
DeviceSize
uniformTexelBufferOffsetAlignmentBytes <- forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
192 :: Ptr DeviceSize))
Bool32
uniformTexelBufferOffsetSingleTexelAlignment <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
200 :: Ptr Bool32))
DeviceSize
maxBufferSize <- forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr PhysicalDeviceVulkan13Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
208 :: Ptr DeviceSize))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Word32
-> Word32
-> Word32
-> ShaderStageFlags
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> DeviceSize
-> Bool
-> DeviceSize
-> Bool
-> DeviceSize
-> PhysicalDeviceVulkan13Properties
PhysicalDeviceVulkan13Properties
Word32
minSubgroupSize
Word32
maxSubgroupSize
Word32
maxComputeWorkgroupSubgroups
ShaderStageFlags
requiredSubgroupSizeStages
Word32
maxInlineUniformBlockSize
Word32
maxPerStageDescriptorInlineUniformBlocks
Word32
maxPerStageDescriptorUpdateAfterBindInlineUniformBlocks
Word32
maxDescriptorSetInlineUniformBlocks
Word32
maxDescriptorSetUpdateAfterBindInlineUniformBlocks
Word32
maxInlineUniformTotalSize
(Bool32 -> Bool
bool32ToBool Bool32
integerDotProduct8BitUnsignedAccelerated)
(Bool32 -> Bool
bool32ToBool Bool32
integerDotProduct8BitSignedAccelerated)
(Bool32 -> Bool
bool32ToBool Bool32
integerDotProduct8BitMixedSignednessAccelerated)
(Bool32 -> Bool
bool32ToBool Bool32
integerDotProduct4x8BitPackedUnsignedAccelerated)
(Bool32 -> Bool
bool32ToBool Bool32
integerDotProduct4x8BitPackedSignedAccelerated)
(Bool32 -> Bool
bool32ToBool Bool32
integerDotProduct4x8BitPackedMixedSignednessAccelerated)
(Bool32 -> Bool
bool32ToBool Bool32
integerDotProduct16BitUnsignedAccelerated)
(Bool32 -> Bool
bool32ToBool Bool32
integerDotProduct16BitSignedAccelerated)
(Bool32 -> Bool
bool32ToBool Bool32
integerDotProduct16BitMixedSignednessAccelerated)
(Bool32 -> Bool
bool32ToBool Bool32
integerDotProduct32BitUnsignedAccelerated)
(Bool32 -> Bool
bool32ToBool Bool32
integerDotProduct32BitSignedAccelerated)
(Bool32 -> Bool
bool32ToBool Bool32
integerDotProduct32BitMixedSignednessAccelerated)
(Bool32 -> Bool
bool32ToBool Bool32
integerDotProduct64BitUnsignedAccelerated)
(Bool32 -> Bool
bool32ToBool Bool32
integerDotProduct64BitSignedAccelerated)
(Bool32 -> Bool
bool32ToBool Bool32
integerDotProduct64BitMixedSignednessAccelerated)
(Bool32 -> Bool
bool32ToBool Bool32
integerDotProductAccumulatingSaturating8BitUnsignedAccelerated)
(Bool32 -> Bool
bool32ToBool Bool32
integerDotProductAccumulatingSaturating8BitSignedAccelerated)
(Bool32 -> Bool
bool32ToBool Bool32
integerDotProductAccumulatingSaturating8BitMixedSignednessAccelerated)
(Bool32 -> Bool
bool32ToBool Bool32
integerDotProductAccumulatingSaturating4x8BitPackedUnsignedAccelerated)
(Bool32 -> Bool
bool32ToBool Bool32
integerDotProductAccumulatingSaturating4x8BitPackedSignedAccelerated)
(Bool32 -> Bool
bool32ToBool Bool32
integerDotProductAccumulatingSaturating4x8BitPackedMixedSignednessAccelerated)
(Bool32 -> Bool
bool32ToBool Bool32
integerDotProductAccumulatingSaturating16BitUnsignedAccelerated)
(Bool32 -> Bool
bool32ToBool Bool32
integerDotProductAccumulatingSaturating16BitSignedAccelerated)
(Bool32 -> Bool
bool32ToBool Bool32
integerDotProductAccumulatingSaturating16BitMixedSignednessAccelerated)
(Bool32 -> Bool
bool32ToBool Bool32
integerDotProductAccumulatingSaturating32BitUnsignedAccelerated)
(Bool32 -> Bool
bool32ToBool Bool32
integerDotProductAccumulatingSaturating32BitSignedAccelerated)
(Bool32 -> Bool
bool32ToBool Bool32
integerDotProductAccumulatingSaturating32BitMixedSignednessAccelerated)
(Bool32 -> Bool
bool32ToBool Bool32
integerDotProductAccumulatingSaturating64BitUnsignedAccelerated)
(Bool32 -> Bool
bool32ToBool Bool32
integerDotProductAccumulatingSaturating64BitSignedAccelerated)
(Bool32 -> Bool
bool32ToBool Bool32
integerDotProductAccumulatingSaturating64BitMixedSignednessAccelerated)
DeviceSize
storageTexelBufferOffsetAlignmentBytes
(Bool32 -> Bool
bool32ToBool Bool32
storageTexelBufferOffsetSingleTexelAlignment)
DeviceSize
uniformTexelBufferOffsetAlignmentBytes
(Bool32 -> Bool
bool32ToBool Bool32
uniformTexelBufferOffsetSingleTexelAlignment)
DeviceSize
maxBufferSize
instance Storable PhysicalDeviceVulkan13Properties where
sizeOf :: PhysicalDeviceVulkan13Properties -> Int
sizeOf ~PhysicalDeviceVulkan13Properties
_ = Int
216
alignment :: PhysicalDeviceVulkan13Properties -> Int
alignment ~PhysicalDeviceVulkan13Properties
_ = Int
8
peek :: Ptr PhysicalDeviceVulkan13Properties
-> IO PhysicalDeviceVulkan13Properties
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr PhysicalDeviceVulkan13Properties
-> PhysicalDeviceVulkan13Properties -> IO ()
poke Ptr PhysicalDeviceVulkan13Properties
ptr PhysicalDeviceVulkan13Properties
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceVulkan13Properties
ptr PhysicalDeviceVulkan13Properties
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PhysicalDeviceVulkan13Properties where
zero :: PhysicalDeviceVulkan13Properties
zero = Word32
-> Word32
-> Word32
-> ShaderStageFlags
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> DeviceSize
-> Bool
-> DeviceSize
-> Bool
-> DeviceSize
-> PhysicalDeviceVulkan13Properties
PhysicalDeviceVulkan13Properties
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero