{-# language CPP #-}
module Vulkan.Core12 ( pattern API_VERSION_1_2
, PhysicalDeviceVulkan11Features(..)
, PhysicalDeviceVulkan11Properties(..)
, PhysicalDeviceVulkan12Features(..)
, PhysicalDeviceVulkan12Properties(..)
, StructureType(..)
, module Vulkan.Core12.Enums
, module Vulkan.Core12.Promoted_From_VK_EXT_descriptor_indexing
, module Vulkan.Core12.Promoted_From_VK_EXT_host_query_reset
, module Vulkan.Core12.Promoted_From_VK_EXT_sampler_filter_minmax
, module Vulkan.Core12.Promoted_From_VK_EXT_scalar_block_layout
, module Vulkan.Core12.Promoted_From_VK_EXT_separate_stencil_usage
, module Vulkan.Core12.Promoted_From_VK_KHR_8bit_storage
, module Vulkan.Core12.Promoted_From_VK_KHR_buffer_device_address
, module Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2
, module Vulkan.Core12.Promoted_From_VK_KHR_depth_stencil_resolve
, module Vulkan.Core12.Promoted_From_VK_KHR_draw_indirect_count
, module Vulkan.Core12.Promoted_From_VK_KHR_driver_properties
, module Vulkan.Core12.Promoted_From_VK_KHR_image_format_list
, module Vulkan.Core12.Promoted_From_VK_KHR_imageless_framebuffer
, module Vulkan.Core12.Promoted_From_VK_KHR_separate_depth_stencil_layouts
, module Vulkan.Core12.Promoted_From_VK_KHR_shader_atomic_int64
, module Vulkan.Core12.Promoted_From_VK_KHR_shader_float16_int8
, module Vulkan.Core12.Promoted_From_VK_KHR_shader_float_controls
, module Vulkan.Core12.Promoted_From_VK_KHR_shader_subgroup_extended_types
, module Vulkan.Core12.Promoted_From_VK_KHR_timeline_semaphore
, module Vulkan.Core12.Promoted_From_VK_KHR_uniform_buffer_standard_layout
, module Vulkan.Core12.Promoted_From_VK_KHR_vulkan_memory_model
) where
import Vulkan.Core12.Enums
import Vulkan.Core12.Promoted_From_VK_EXT_descriptor_indexing
import Vulkan.Core12.Promoted_From_VK_EXT_host_query_reset
import Vulkan.Core12.Promoted_From_VK_EXT_sampler_filter_minmax
import Vulkan.Core12.Promoted_From_VK_EXT_scalar_block_layout
import Vulkan.Core12.Promoted_From_VK_EXT_separate_stencil_usage
import Vulkan.Core12.Promoted_From_VK_KHR_8bit_storage
import Vulkan.Core12.Promoted_From_VK_KHR_buffer_device_address
import Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2
import Vulkan.Core12.Promoted_From_VK_KHR_depth_stencil_resolve
import Vulkan.Core12.Promoted_From_VK_KHR_draw_indirect_count
import Vulkan.Core12.Promoted_From_VK_KHR_driver_properties
import Vulkan.Core12.Promoted_From_VK_KHR_image_format_list
import Vulkan.Core12.Promoted_From_VK_KHR_imageless_framebuffer
import Vulkan.Core12.Promoted_From_VK_KHR_separate_depth_stencil_layouts
import Vulkan.Core12.Promoted_From_VK_KHR_shader_atomic_int64
import Vulkan.Core12.Promoted_From_VK_KHR_shader_float16_int8
import Vulkan.Core12.Promoted_From_VK_KHR_shader_float_controls
import Vulkan.Core12.Promoted_From_VK_KHR_shader_subgroup_extended_types
import Vulkan.Core12.Promoted_From_VK_KHR_timeline_semaphore
import Vulkan.Core12.Promoted_From_VK_KHR_uniform_buffer_standard_layout
import Vulkan.Core12.Promoted_From_VK_KHR_vulkan_memory_model
import Vulkan.CStruct.Utils (FixedArray)
import Foreign.Marshal.Alloc (allocaBytes)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import Data.ByteString (packCString)
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.C.Types (CChar)
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.Word (Word64)
import Data.Word (Word8)
import Data.ByteString (ByteString)
import Data.Kind (Type)
import Vulkan.Core10.FundamentalTypes (bool32ToBool)
import Vulkan.Core10.FundamentalTypes (boolToBool32)
import Vulkan.CStruct.Utils (lowerArrayPtr)
import Vulkan.CStruct.Utils (peekByteStringFromSizedVectorPtr)
import Vulkan.CStruct.Utils (pokeFixedLengthByteString)
import Vulkan.CStruct.Utils (pokeFixedLengthNullTerminatedByteString)
import Vulkan.Core10.FundamentalTypes (Bool32)
import Vulkan.Core12.Promoted_From_VK_KHR_driver_properties (ConformanceVersion)
import Vulkan.Core10.FundamentalTypes (DeviceSize)
import Vulkan.Core12.Enums.DriverId (DriverId)
import Vulkan.Core10.APIConstants (LUID_SIZE)
import Vulkan.Core10.APIConstants (MAX_DRIVER_INFO_SIZE)
import Vulkan.Core10.APIConstants (MAX_DRIVER_NAME_SIZE)
import Vulkan.Core11.Enums.PointClippingBehavior (PointClippingBehavior)
import Vulkan.Core12.Enums.ResolveModeFlagBits (ResolveModeFlags)
import Vulkan.Core10.Enums.SampleCountFlagBits (SampleCountFlags)
import Vulkan.Core12.Enums.ShaderFloatControlsIndependence (ShaderFloatControlsIndependence)
import Vulkan.Core10.Enums.ShaderStageFlagBits (ShaderStageFlags)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Core11.Enums.SubgroupFeatureFlagBits (SubgroupFeatureFlags)
import Vulkan.Core10.APIConstants (UUID_SIZE)
import Vulkan.Version (pattern MAKE_API_VERSION)
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_VULKAN_1_1_FEATURES))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_VULKAN_1_1_PROPERTIES))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_VULKAN_1_2_FEATURES))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_VULKAN_1_2_PROPERTIES))
import Vulkan.Core10.Enums.StructureType (StructureType(..))
pattern API_VERSION_1_2 :: Word32
pattern $bAPI_VERSION_1_2 :: Word32
$mAPI_VERSION_1_2 :: forall {r}. Word32 -> ((# #) -> r) -> ((# #) -> r) -> r
API_VERSION_1_2 = MAKE_API_VERSION 1 2 0
data PhysicalDeviceVulkan11Features = PhysicalDeviceVulkan11Features
{
PhysicalDeviceVulkan11Features -> Bool
storageBuffer16BitAccess :: Bool
,
PhysicalDeviceVulkan11Features -> Bool
uniformAndStorageBuffer16BitAccess :: Bool
,
PhysicalDeviceVulkan11Features -> Bool
storagePushConstant16 :: Bool
,
PhysicalDeviceVulkan11Features -> Bool
storageInputOutput16 :: Bool
,
PhysicalDeviceVulkan11Features -> Bool
multiview :: Bool
,
PhysicalDeviceVulkan11Features -> Bool
multiviewGeometryShader :: Bool
,
PhysicalDeviceVulkan11Features -> Bool
multiviewTessellationShader :: Bool
,
:: Bool
,
PhysicalDeviceVulkan11Features -> Bool
variablePointers :: Bool
,
PhysicalDeviceVulkan11Features -> Bool
protectedMemory :: Bool
,
PhysicalDeviceVulkan11Features -> Bool
samplerYcbcrConversion :: Bool
,
PhysicalDeviceVulkan11Features -> Bool
shaderDrawParameters :: Bool
}
deriving (Typeable, PhysicalDeviceVulkan11Features
-> PhysicalDeviceVulkan11Features -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceVulkan11Features
-> PhysicalDeviceVulkan11Features -> Bool
$c/= :: PhysicalDeviceVulkan11Features
-> PhysicalDeviceVulkan11Features -> Bool
== :: PhysicalDeviceVulkan11Features
-> PhysicalDeviceVulkan11Features -> Bool
$c== :: PhysicalDeviceVulkan11Features
-> PhysicalDeviceVulkan11Features -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceVulkan11Features)
#endif
deriving instance Show PhysicalDeviceVulkan11Features
instance ToCStruct PhysicalDeviceVulkan11Features where
withCStruct :: forall b.
PhysicalDeviceVulkan11Features
-> (Ptr PhysicalDeviceVulkan11Features -> IO b) -> IO b
withCStruct PhysicalDeviceVulkan11Features
x Ptr PhysicalDeviceVulkan11Features -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
64 forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceVulkan11Features
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceVulkan11Features
p PhysicalDeviceVulkan11Features
x (Ptr PhysicalDeviceVulkan11Features -> IO b
f Ptr PhysicalDeviceVulkan11Features
p)
pokeCStruct :: forall b.
Ptr PhysicalDeviceVulkan11Features
-> PhysicalDeviceVulkan11Features -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceVulkan11Features
p PhysicalDeviceVulkan11Features{Bool
shaderDrawParameters :: Bool
samplerYcbcrConversion :: Bool
protectedMemory :: Bool
variablePointers :: Bool
variablePointersStorageBuffer :: Bool
multiviewTessellationShader :: Bool
multiviewGeometryShader :: Bool
multiview :: Bool
storageInputOutput16 :: Bool
storagePushConstant16 :: Bool
uniformAndStorageBuffer16BitAccess :: Bool
storageBuffer16BitAccess :: Bool
$sel:shaderDrawParameters:PhysicalDeviceVulkan11Features :: PhysicalDeviceVulkan11Features -> Bool
$sel:samplerYcbcrConversion:PhysicalDeviceVulkan11Features :: PhysicalDeviceVulkan11Features -> Bool
$sel:protectedMemory:PhysicalDeviceVulkan11Features :: PhysicalDeviceVulkan11Features -> Bool
$sel:variablePointers:PhysicalDeviceVulkan11Features :: PhysicalDeviceVulkan11Features -> Bool
$sel:variablePointersStorageBuffer:PhysicalDeviceVulkan11Features :: PhysicalDeviceVulkan11Features -> Bool
$sel:multiviewTessellationShader:PhysicalDeviceVulkan11Features :: PhysicalDeviceVulkan11Features -> Bool
$sel:multiviewGeometryShader:PhysicalDeviceVulkan11Features :: PhysicalDeviceVulkan11Features -> Bool
$sel:multiview:PhysicalDeviceVulkan11Features :: PhysicalDeviceVulkan11Features -> Bool
$sel:storageInputOutput16:PhysicalDeviceVulkan11Features :: PhysicalDeviceVulkan11Features -> Bool
$sel:storagePushConstant16:PhysicalDeviceVulkan11Features :: PhysicalDeviceVulkan11Features -> Bool
$sel:uniformAndStorageBuffer16BitAccess:PhysicalDeviceVulkan11Features :: PhysicalDeviceVulkan11Features -> Bool
$sel:storageBuffer16BitAccess:PhysicalDeviceVulkan11Features :: PhysicalDeviceVulkan11Features -> Bool
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_VULKAN_1_1_FEATURES)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Features
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 PhysicalDeviceVulkan11Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
storageBuffer16BitAccess))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
uniformAndStorageBuffer16BitAccess))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
storagePushConstant16))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
storageInputOutput16))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
multiview))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
36 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
multiviewGeometryShader))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
multiviewTessellationShader))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
44 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
variablePointersStorageBuffer))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
variablePointers))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
52 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
protectedMemory))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
samplerYcbcrConversion))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
60 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderDrawParameters))
IO b
f
cStructSize :: Int
cStructSize = Int
64
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b. Ptr PhysicalDeviceVulkan11Features -> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceVulkan11Features
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_VULKAN_1_1_FEATURES)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Features
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 PhysicalDeviceVulkan11Features
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 PhysicalDeviceVulkan11Features
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 PhysicalDeviceVulkan11Features
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 PhysicalDeviceVulkan11Features
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 PhysicalDeviceVulkan11Features
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 PhysicalDeviceVulkan11Features
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 PhysicalDeviceVulkan11Features
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 PhysicalDeviceVulkan11Features
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 PhysicalDeviceVulkan11Features
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 PhysicalDeviceVulkan11Features
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 PhysicalDeviceVulkan11Features
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 PhysicalDeviceVulkan11Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
60 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
IO b
f
instance FromCStruct PhysicalDeviceVulkan11Features where
peekCStruct :: Ptr PhysicalDeviceVulkan11Features
-> IO PhysicalDeviceVulkan11Features
peekCStruct Ptr PhysicalDeviceVulkan11Features
p = do
Bool32
storageBuffer16BitAccess <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan11Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32))
Bool32
uniformAndStorageBuffer16BitAccess <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan11Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32))
Bool32
storagePushConstant16 <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan11Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Bool32))
Bool32
storageInputOutput16 <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan11Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr Bool32))
Bool32
multiview <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan11Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr Bool32))
Bool32
multiviewGeometryShader <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan11Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
36 :: Ptr Bool32))
Bool32
multiviewTessellationShader <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan11Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr Bool32))
Bool32
variablePointersStorageBuffer <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan11Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
44 :: Ptr Bool32))
Bool32
variablePointers <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan11Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48 :: Ptr Bool32))
Bool32
protectedMemory <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan11Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
52 :: Ptr Bool32))
Bool32
samplerYcbcrConversion <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan11Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56 :: Ptr Bool32))
Bool32
shaderDrawParameters <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan11Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
60 :: 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
-> PhysicalDeviceVulkan11Features
PhysicalDeviceVulkan11Features
(Bool32 -> Bool
bool32ToBool Bool32
storageBuffer16BitAccess)
(Bool32 -> Bool
bool32ToBool Bool32
uniformAndStorageBuffer16BitAccess)
(Bool32 -> Bool
bool32ToBool Bool32
storagePushConstant16)
(Bool32 -> Bool
bool32ToBool Bool32
storageInputOutput16)
(Bool32 -> Bool
bool32ToBool Bool32
multiview)
(Bool32 -> Bool
bool32ToBool Bool32
multiviewGeometryShader)
(Bool32 -> Bool
bool32ToBool Bool32
multiviewTessellationShader)
(Bool32 -> Bool
bool32ToBool Bool32
variablePointersStorageBuffer)
(Bool32 -> Bool
bool32ToBool Bool32
variablePointers)
(Bool32 -> Bool
bool32ToBool Bool32
protectedMemory)
(Bool32 -> Bool
bool32ToBool Bool32
samplerYcbcrConversion)
(Bool32 -> Bool
bool32ToBool Bool32
shaderDrawParameters)
instance Storable PhysicalDeviceVulkan11Features where
sizeOf :: PhysicalDeviceVulkan11Features -> Int
sizeOf ~PhysicalDeviceVulkan11Features
_ = Int
64
alignment :: PhysicalDeviceVulkan11Features -> Int
alignment ~PhysicalDeviceVulkan11Features
_ = Int
8
peek :: Ptr PhysicalDeviceVulkan11Features
-> IO PhysicalDeviceVulkan11Features
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr PhysicalDeviceVulkan11Features
-> PhysicalDeviceVulkan11Features -> IO ()
poke Ptr PhysicalDeviceVulkan11Features
ptr PhysicalDeviceVulkan11Features
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceVulkan11Features
ptr PhysicalDeviceVulkan11Features
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PhysicalDeviceVulkan11Features where
zero :: PhysicalDeviceVulkan11Features
zero = Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> PhysicalDeviceVulkan11Features
PhysicalDeviceVulkan11Features
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 PhysicalDeviceVulkan11Properties = PhysicalDeviceVulkan11Properties
{
PhysicalDeviceVulkan11Properties -> ByteString
deviceUUID :: ByteString
,
PhysicalDeviceVulkan11Properties -> ByteString
driverUUID :: ByteString
,
PhysicalDeviceVulkan11Properties -> ByteString
deviceLUID :: ByteString
,
PhysicalDeviceVulkan11Properties -> Word32
deviceNodeMask :: Word32
,
PhysicalDeviceVulkan11Properties -> Bool
deviceLUIDValid :: Bool
,
PhysicalDeviceVulkan11Properties -> Word32
subgroupSize :: Word32
,
PhysicalDeviceVulkan11Properties -> ShaderStageFlags
subgroupSupportedStages :: ShaderStageFlags
,
PhysicalDeviceVulkan11Properties -> SubgroupFeatureFlags
subgroupSupportedOperations :: SubgroupFeatureFlags
,
PhysicalDeviceVulkan11Properties -> Bool
subgroupQuadOperationsInAllStages :: Bool
,
PhysicalDeviceVulkan11Properties -> PointClippingBehavior
pointClippingBehavior :: PointClippingBehavior
,
PhysicalDeviceVulkan11Properties -> Word32
maxMultiviewViewCount :: Word32
,
PhysicalDeviceVulkan11Properties -> Word32
maxMultiviewInstanceIndex :: Word32
,
PhysicalDeviceVulkan11Properties -> Bool
protectedNoFault :: Bool
,
PhysicalDeviceVulkan11Properties -> Word32
maxPerSetDescriptors :: Word32
,
PhysicalDeviceVulkan11Properties -> DeviceSize
maxMemoryAllocationSize :: DeviceSize
}
deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceVulkan11Properties)
#endif
deriving instance Show PhysicalDeviceVulkan11Properties
instance ToCStruct PhysicalDeviceVulkan11Properties where
withCStruct :: forall b.
PhysicalDeviceVulkan11Properties
-> (Ptr PhysicalDeviceVulkan11Properties -> IO b) -> IO b
withCStruct PhysicalDeviceVulkan11Properties
x Ptr PhysicalDeviceVulkan11Properties -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
112 forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceVulkan11Properties
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceVulkan11Properties
p PhysicalDeviceVulkan11Properties
x (Ptr PhysicalDeviceVulkan11Properties -> IO b
f Ptr PhysicalDeviceVulkan11Properties
p)
pokeCStruct :: forall b.
Ptr PhysicalDeviceVulkan11Properties
-> PhysicalDeviceVulkan11Properties -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceVulkan11Properties
p PhysicalDeviceVulkan11Properties{Bool
Word32
DeviceSize
ByteString
ShaderStageFlags
PointClippingBehavior
SubgroupFeatureFlags
maxMemoryAllocationSize :: DeviceSize
maxPerSetDescriptors :: Word32
protectedNoFault :: Bool
maxMultiviewInstanceIndex :: Word32
maxMultiviewViewCount :: Word32
pointClippingBehavior :: PointClippingBehavior
subgroupQuadOperationsInAllStages :: Bool
subgroupSupportedOperations :: SubgroupFeatureFlags
subgroupSupportedStages :: ShaderStageFlags
subgroupSize :: Word32
deviceLUIDValid :: Bool
deviceNodeMask :: Word32
deviceLUID :: ByteString
driverUUID :: ByteString
deviceUUID :: ByteString
$sel:maxMemoryAllocationSize:PhysicalDeviceVulkan11Properties :: PhysicalDeviceVulkan11Properties -> DeviceSize
$sel:maxPerSetDescriptors:PhysicalDeviceVulkan11Properties :: PhysicalDeviceVulkan11Properties -> Word32
$sel:protectedNoFault:PhysicalDeviceVulkan11Properties :: PhysicalDeviceVulkan11Properties -> Bool
$sel:maxMultiviewInstanceIndex:PhysicalDeviceVulkan11Properties :: PhysicalDeviceVulkan11Properties -> Word32
$sel:maxMultiviewViewCount:PhysicalDeviceVulkan11Properties :: PhysicalDeviceVulkan11Properties -> Word32
$sel:pointClippingBehavior:PhysicalDeviceVulkan11Properties :: PhysicalDeviceVulkan11Properties -> PointClippingBehavior
$sel:subgroupQuadOperationsInAllStages:PhysicalDeviceVulkan11Properties :: PhysicalDeviceVulkan11Properties -> Bool
$sel:subgroupSupportedOperations:PhysicalDeviceVulkan11Properties :: PhysicalDeviceVulkan11Properties -> SubgroupFeatureFlags
$sel:subgroupSupportedStages:PhysicalDeviceVulkan11Properties :: PhysicalDeviceVulkan11Properties -> ShaderStageFlags
$sel:subgroupSize:PhysicalDeviceVulkan11Properties :: PhysicalDeviceVulkan11Properties -> Word32
$sel:deviceLUIDValid:PhysicalDeviceVulkan11Properties :: PhysicalDeviceVulkan11Properties -> Bool
$sel:deviceNodeMask:PhysicalDeviceVulkan11Properties :: PhysicalDeviceVulkan11Properties -> Word32
$sel:deviceLUID:PhysicalDeviceVulkan11Properties :: PhysicalDeviceVulkan11Properties -> ByteString
$sel:driverUUID:PhysicalDeviceVulkan11Properties :: PhysicalDeviceVulkan11Properties -> ByteString
$sel:deviceUUID:PhysicalDeviceVulkan11Properties :: PhysicalDeviceVulkan11Properties -> ByteString
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_VULKAN_1_1_PROPERTIES)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall (n :: Nat).
KnownNat n =>
Ptr (FixedArray n Word8) -> ByteString -> IO ()
pokeFixedLengthByteString ((Ptr PhysicalDeviceVulkan11Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr (FixedArray UUID_SIZE Word8))) (ByteString
deviceUUID)
forall (n :: Nat).
KnownNat n =>
Ptr (FixedArray n Word8) -> ByteString -> IO ()
pokeFixedLengthByteString ((Ptr PhysicalDeviceVulkan11Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr (FixedArray UUID_SIZE Word8))) (ByteString
driverUUID)
forall (n :: Nat).
KnownNat n =>
Ptr (FixedArray n Word8) -> ByteString -> IO ()
pokeFixedLengthByteString ((Ptr PhysicalDeviceVulkan11Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48 :: Ptr (FixedArray LUID_SIZE Word8))) (ByteString
deviceLUID)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56 :: Ptr Word32)) (Word32
deviceNodeMask)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
60 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
deviceLUIDValid))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
64 :: Ptr Word32)) (Word32
subgroupSize)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
68 :: Ptr ShaderStageFlags)) (ShaderStageFlags
subgroupSupportedStages)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
72 :: Ptr SubgroupFeatureFlags)) (SubgroupFeatureFlags
subgroupSupportedOperations)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
76 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
subgroupQuadOperationsInAllStages))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
80 :: Ptr PointClippingBehavior)) (PointClippingBehavior
pointClippingBehavior)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
84 :: Ptr Word32)) (Word32
maxMultiviewViewCount)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
88 :: Ptr Word32)) (Word32
maxMultiviewInstanceIndex)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
92 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
protectedNoFault))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
96 :: Ptr Word32)) (Word32
maxPerSetDescriptors)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
104 :: Ptr DeviceSize)) (DeviceSize
maxMemoryAllocationSize)
IO b
f
cStructSize :: Int
cStructSize = Int
112
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b. Ptr PhysicalDeviceVulkan11Properties -> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceVulkan11Properties
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_VULKAN_1_1_PROPERTIES)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall (n :: Nat).
KnownNat n =>
Ptr (FixedArray n Word8) -> ByteString -> IO ()
pokeFixedLengthByteString ((Ptr PhysicalDeviceVulkan11Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr (FixedArray UUID_SIZE Word8))) (forall a. Monoid a => a
mempty)
forall (n :: Nat).
KnownNat n =>
Ptr (FixedArray n Word8) -> ByteString -> IO ()
pokeFixedLengthByteString ((Ptr PhysicalDeviceVulkan11Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr (FixedArray UUID_SIZE Word8))) (forall a. Monoid a => a
mempty)
forall (n :: Nat).
KnownNat n =>
Ptr (FixedArray n Word8) -> ByteString -> IO ()
pokeFixedLengthByteString ((Ptr PhysicalDeviceVulkan11Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48 :: Ptr (FixedArray LUID_SIZE Word8))) (forall a. Monoid a => a
mempty)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56 :: Ptr Word32)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Properties
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 PhysicalDeviceVulkan11Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
64 :: Ptr Word32)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
68 :: Ptr ShaderStageFlags)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
72 :: Ptr SubgroupFeatureFlags)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Properties
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 PhysicalDeviceVulkan11Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
80 :: Ptr PointClippingBehavior)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
84 :: Ptr Word32)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
88 :: Ptr Word32)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Properties
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 PhysicalDeviceVulkan11Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
96 :: Ptr Word32)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
104 :: Ptr DeviceSize)) (forall a. Zero a => a
zero)
IO b
f
instance FromCStruct PhysicalDeviceVulkan11Properties where
peekCStruct :: Ptr PhysicalDeviceVulkan11Properties
-> IO PhysicalDeviceVulkan11Properties
peekCStruct Ptr PhysicalDeviceVulkan11Properties
p = do
ByteString
deviceUUID <- forall (n :: Nat).
KnownNat n =>
Ptr (FixedArray n Word8) -> IO ByteString
peekByteStringFromSizedVectorPtr ((Ptr PhysicalDeviceVulkan11Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr (FixedArray UUID_SIZE Word8)))
ByteString
driverUUID <- forall (n :: Nat).
KnownNat n =>
Ptr (FixedArray n Word8) -> IO ByteString
peekByteStringFromSizedVectorPtr ((Ptr PhysicalDeviceVulkan11Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr (FixedArray UUID_SIZE Word8)))
ByteString
deviceLUID <- forall (n :: Nat).
KnownNat n =>
Ptr (FixedArray n Word8) -> IO ByteString
peekByteStringFromSizedVectorPtr ((Ptr PhysicalDeviceVulkan11Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48 :: Ptr (FixedArray LUID_SIZE Word8)))
Word32
deviceNodeMask <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceVulkan11Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56 :: Ptr Word32))
Bool32
deviceLUIDValid <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan11Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
60 :: Ptr Bool32))
Word32
subgroupSize <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceVulkan11Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
64 :: Ptr Word32))
ShaderStageFlags
subgroupSupportedStages <- forall a. Storable a => Ptr a -> IO a
peek @ShaderStageFlags ((Ptr PhysicalDeviceVulkan11Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
68 :: Ptr ShaderStageFlags))
SubgroupFeatureFlags
subgroupSupportedOperations <- forall a. Storable a => Ptr a -> IO a
peek @SubgroupFeatureFlags ((Ptr PhysicalDeviceVulkan11Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
72 :: Ptr SubgroupFeatureFlags))
Bool32
subgroupQuadOperationsInAllStages <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan11Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
76 :: Ptr Bool32))
PointClippingBehavior
pointClippingBehavior <- forall a. Storable a => Ptr a -> IO a
peek @PointClippingBehavior ((Ptr PhysicalDeviceVulkan11Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
80 :: Ptr PointClippingBehavior))
Word32
maxMultiviewViewCount <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceVulkan11Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
84 :: Ptr Word32))
Word32
maxMultiviewInstanceIndex <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceVulkan11Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
88 :: Ptr Word32))
Bool32
protectedNoFault <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan11Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
92 :: Ptr Bool32))
Word32
maxPerSetDescriptors <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceVulkan11Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
96 :: Ptr Word32))
DeviceSize
maxMemoryAllocationSize <- forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr PhysicalDeviceVulkan11Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
104 :: Ptr DeviceSize))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ ByteString
-> ByteString
-> ByteString
-> Word32
-> Bool
-> Word32
-> ShaderStageFlags
-> SubgroupFeatureFlags
-> Bool
-> PointClippingBehavior
-> Word32
-> Word32
-> Bool
-> Word32
-> DeviceSize
-> PhysicalDeviceVulkan11Properties
PhysicalDeviceVulkan11Properties
ByteString
deviceUUID
ByteString
driverUUID
ByteString
deviceLUID
Word32
deviceNodeMask
(Bool32 -> Bool
bool32ToBool Bool32
deviceLUIDValid)
Word32
subgroupSize
ShaderStageFlags
subgroupSupportedStages
SubgroupFeatureFlags
subgroupSupportedOperations
(Bool32 -> Bool
bool32ToBool Bool32
subgroupQuadOperationsInAllStages)
PointClippingBehavior
pointClippingBehavior
Word32
maxMultiviewViewCount
Word32
maxMultiviewInstanceIndex
(Bool32 -> Bool
bool32ToBool Bool32
protectedNoFault)
Word32
maxPerSetDescriptors
DeviceSize
maxMemoryAllocationSize
instance Storable PhysicalDeviceVulkan11Properties where
sizeOf :: PhysicalDeviceVulkan11Properties -> Int
sizeOf ~PhysicalDeviceVulkan11Properties
_ = Int
112
alignment :: PhysicalDeviceVulkan11Properties -> Int
alignment ~PhysicalDeviceVulkan11Properties
_ = Int
8
peek :: Ptr PhysicalDeviceVulkan11Properties
-> IO PhysicalDeviceVulkan11Properties
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr PhysicalDeviceVulkan11Properties
-> PhysicalDeviceVulkan11Properties -> IO ()
poke Ptr PhysicalDeviceVulkan11Properties
ptr PhysicalDeviceVulkan11Properties
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceVulkan11Properties
ptr PhysicalDeviceVulkan11Properties
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PhysicalDeviceVulkan11Properties where
zero :: PhysicalDeviceVulkan11Properties
zero = ByteString
-> ByteString
-> ByteString
-> Word32
-> Bool
-> Word32
-> ShaderStageFlags
-> SubgroupFeatureFlags
-> Bool
-> PointClippingBehavior
-> Word32
-> Word32
-> Bool
-> Word32
-> DeviceSize
-> PhysicalDeviceVulkan11Properties
PhysicalDeviceVulkan11Properties
forall a. Monoid a => a
mempty
forall a. Monoid a => a
mempty
forall a. Monoid a => a
mempty
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 PhysicalDeviceVulkan12Features = PhysicalDeviceVulkan12Features
{
PhysicalDeviceVulkan12Features -> Bool
samplerMirrorClampToEdge :: Bool
,
PhysicalDeviceVulkan12Features -> Bool
drawIndirectCount :: Bool
,
PhysicalDeviceVulkan12Features -> Bool
storageBuffer8BitAccess :: Bool
,
PhysicalDeviceVulkan12Features -> Bool
uniformAndStorageBuffer8BitAccess :: Bool
,
PhysicalDeviceVulkan12Features -> Bool
storagePushConstant8 :: Bool
,
PhysicalDeviceVulkan12Features -> Bool
shaderBufferInt64Atomics :: Bool
,
PhysicalDeviceVulkan12Features -> Bool
shaderSharedInt64Atomics :: Bool
,
PhysicalDeviceVulkan12Features -> Bool
shaderFloat16 :: Bool
,
PhysicalDeviceVulkan12Features -> Bool
shaderInt8 :: Bool
,
PhysicalDeviceVulkan12Features -> Bool
descriptorIndexing :: Bool
,
PhysicalDeviceVulkan12Features -> Bool
shaderInputAttachmentArrayDynamicIndexing :: Bool
,
PhysicalDeviceVulkan12Features -> Bool
shaderUniformTexelBufferArrayDynamicIndexing :: Bool
,
PhysicalDeviceVulkan12Features -> Bool
shaderStorageTexelBufferArrayDynamicIndexing :: Bool
,
PhysicalDeviceVulkan12Features -> Bool
shaderUniformBufferArrayNonUniformIndexing :: Bool
,
PhysicalDeviceVulkan12Features -> Bool
shaderSampledImageArrayNonUniformIndexing :: Bool
,
PhysicalDeviceVulkan12Features -> Bool
shaderStorageBufferArrayNonUniformIndexing :: Bool
,
PhysicalDeviceVulkan12Features -> Bool
shaderStorageImageArrayNonUniformIndexing :: Bool
,
PhysicalDeviceVulkan12Features -> Bool
shaderInputAttachmentArrayNonUniformIndexing :: Bool
,
PhysicalDeviceVulkan12Features -> Bool
shaderUniformTexelBufferArrayNonUniformIndexing :: Bool
,
PhysicalDeviceVulkan12Features -> Bool
shaderStorageTexelBufferArrayNonUniformIndexing :: Bool
,
PhysicalDeviceVulkan12Features -> Bool
descriptorBindingUniformBufferUpdateAfterBind :: Bool
,
PhysicalDeviceVulkan12Features -> Bool
descriptorBindingSampledImageUpdateAfterBind :: Bool
,
PhysicalDeviceVulkan12Features -> Bool
descriptorBindingStorageImageUpdateAfterBind :: Bool
,
PhysicalDeviceVulkan12Features -> Bool
descriptorBindingStorageBufferUpdateAfterBind :: Bool
,
PhysicalDeviceVulkan12Features -> Bool
descriptorBindingUniformTexelBufferUpdateAfterBind :: Bool
,
PhysicalDeviceVulkan12Features -> Bool
descriptorBindingStorageTexelBufferUpdateAfterBind :: Bool
,
PhysicalDeviceVulkan12Features -> Bool
descriptorBindingUpdateUnusedWhilePending :: Bool
,
PhysicalDeviceVulkan12Features -> Bool
descriptorBindingPartiallyBound :: Bool
,
PhysicalDeviceVulkan12Features -> Bool
descriptorBindingVariableDescriptorCount :: Bool
,
PhysicalDeviceVulkan12Features -> Bool
runtimeDescriptorArray :: Bool
,
PhysicalDeviceVulkan12Features -> Bool
samplerFilterMinmax :: Bool
,
PhysicalDeviceVulkan12Features -> Bool
scalarBlockLayout :: Bool
,
PhysicalDeviceVulkan12Features -> Bool
imagelessFramebuffer :: Bool
,
PhysicalDeviceVulkan12Features -> Bool
uniformBufferStandardLayout :: Bool
,
PhysicalDeviceVulkan12Features -> Bool
shaderSubgroupExtendedTypes :: Bool
,
PhysicalDeviceVulkan12Features -> Bool
separateDepthStencilLayouts :: Bool
,
PhysicalDeviceVulkan12Features -> Bool
hostQueryReset :: Bool
,
PhysicalDeviceVulkan12Features -> Bool
timelineSemaphore :: Bool
,
PhysicalDeviceVulkan12Features -> Bool
bufferDeviceAddress :: Bool
,
PhysicalDeviceVulkan12Features -> Bool
bufferDeviceAddressCaptureReplay :: Bool
,
PhysicalDeviceVulkan12Features -> Bool
bufferDeviceAddressMultiDevice :: Bool
,
PhysicalDeviceVulkan12Features -> Bool
vulkanMemoryModel :: Bool
,
PhysicalDeviceVulkan12Features -> Bool
vulkanMemoryModelDeviceScope :: Bool
,
PhysicalDeviceVulkan12Features -> Bool
vulkanMemoryModelAvailabilityVisibilityChains :: Bool
,
PhysicalDeviceVulkan12Features -> Bool
shaderOutputViewportIndex :: Bool
,
PhysicalDeviceVulkan12Features -> Bool
shaderOutputLayer :: Bool
,
PhysicalDeviceVulkan12Features -> Bool
subgroupBroadcastDynamicId :: Bool
}
deriving (Typeable, PhysicalDeviceVulkan12Features
-> PhysicalDeviceVulkan12Features -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceVulkan12Features
-> PhysicalDeviceVulkan12Features -> Bool
$c/= :: PhysicalDeviceVulkan12Features
-> PhysicalDeviceVulkan12Features -> Bool
== :: PhysicalDeviceVulkan12Features
-> PhysicalDeviceVulkan12Features -> Bool
$c== :: PhysicalDeviceVulkan12Features
-> PhysicalDeviceVulkan12Features -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceVulkan12Features)
#endif
deriving instance Show PhysicalDeviceVulkan12Features
instance ToCStruct PhysicalDeviceVulkan12Features where
withCStruct :: forall b.
PhysicalDeviceVulkan12Features
-> (Ptr PhysicalDeviceVulkan12Features -> IO b) -> IO b
withCStruct PhysicalDeviceVulkan12Features
x Ptr PhysicalDeviceVulkan12Features -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
208 forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceVulkan12Features
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceVulkan12Features
p PhysicalDeviceVulkan12Features
x (Ptr PhysicalDeviceVulkan12Features -> IO b
f Ptr PhysicalDeviceVulkan12Features
p)
pokeCStruct :: forall b.
Ptr PhysicalDeviceVulkan12Features
-> PhysicalDeviceVulkan12Features -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceVulkan12Features
p PhysicalDeviceVulkan12Features{Bool
subgroupBroadcastDynamicId :: Bool
shaderOutputLayer :: Bool
shaderOutputViewportIndex :: Bool
vulkanMemoryModelAvailabilityVisibilityChains :: Bool
vulkanMemoryModelDeviceScope :: Bool
vulkanMemoryModel :: Bool
bufferDeviceAddressMultiDevice :: Bool
bufferDeviceAddressCaptureReplay :: Bool
bufferDeviceAddress :: Bool
timelineSemaphore :: Bool
hostQueryReset :: Bool
separateDepthStencilLayouts :: Bool
shaderSubgroupExtendedTypes :: Bool
uniformBufferStandardLayout :: Bool
imagelessFramebuffer :: Bool
scalarBlockLayout :: Bool
samplerFilterMinmax :: Bool
runtimeDescriptorArray :: Bool
descriptorBindingVariableDescriptorCount :: Bool
descriptorBindingPartiallyBound :: Bool
descriptorBindingUpdateUnusedWhilePending :: Bool
descriptorBindingStorageTexelBufferUpdateAfterBind :: Bool
descriptorBindingUniformTexelBufferUpdateAfterBind :: Bool
descriptorBindingStorageBufferUpdateAfterBind :: Bool
descriptorBindingStorageImageUpdateAfterBind :: Bool
descriptorBindingSampledImageUpdateAfterBind :: Bool
descriptorBindingUniformBufferUpdateAfterBind :: Bool
shaderStorageTexelBufferArrayNonUniformIndexing :: Bool
shaderUniformTexelBufferArrayNonUniformIndexing :: Bool
shaderInputAttachmentArrayNonUniformIndexing :: Bool
shaderStorageImageArrayNonUniformIndexing :: Bool
shaderStorageBufferArrayNonUniformIndexing :: Bool
shaderSampledImageArrayNonUniformIndexing :: Bool
shaderUniformBufferArrayNonUniformIndexing :: Bool
shaderStorageTexelBufferArrayDynamicIndexing :: Bool
shaderUniformTexelBufferArrayDynamicIndexing :: Bool
shaderInputAttachmentArrayDynamicIndexing :: Bool
descriptorIndexing :: Bool
shaderInt8 :: Bool
shaderFloat16 :: Bool
shaderSharedInt64Atomics :: Bool
shaderBufferInt64Atomics :: Bool
storagePushConstant8 :: Bool
uniformAndStorageBuffer8BitAccess :: Bool
storageBuffer8BitAccess :: Bool
drawIndirectCount :: Bool
samplerMirrorClampToEdge :: Bool
$sel:subgroupBroadcastDynamicId:PhysicalDeviceVulkan12Features :: PhysicalDeviceVulkan12Features -> Bool
$sel:shaderOutputLayer:PhysicalDeviceVulkan12Features :: PhysicalDeviceVulkan12Features -> Bool
$sel:shaderOutputViewportIndex:PhysicalDeviceVulkan12Features :: PhysicalDeviceVulkan12Features -> Bool
$sel:vulkanMemoryModelAvailabilityVisibilityChains:PhysicalDeviceVulkan12Features :: PhysicalDeviceVulkan12Features -> Bool
$sel:vulkanMemoryModelDeviceScope:PhysicalDeviceVulkan12Features :: PhysicalDeviceVulkan12Features -> Bool
$sel:vulkanMemoryModel:PhysicalDeviceVulkan12Features :: PhysicalDeviceVulkan12Features -> Bool
$sel:bufferDeviceAddressMultiDevice:PhysicalDeviceVulkan12Features :: PhysicalDeviceVulkan12Features -> Bool
$sel:bufferDeviceAddressCaptureReplay:PhysicalDeviceVulkan12Features :: PhysicalDeviceVulkan12Features -> Bool
$sel:bufferDeviceAddress:PhysicalDeviceVulkan12Features :: PhysicalDeviceVulkan12Features -> Bool
$sel:timelineSemaphore:PhysicalDeviceVulkan12Features :: PhysicalDeviceVulkan12Features -> Bool
$sel:hostQueryReset:PhysicalDeviceVulkan12Features :: PhysicalDeviceVulkan12Features -> Bool
$sel:separateDepthStencilLayouts:PhysicalDeviceVulkan12Features :: PhysicalDeviceVulkan12Features -> Bool
$sel:shaderSubgroupExtendedTypes:PhysicalDeviceVulkan12Features :: PhysicalDeviceVulkan12Features -> Bool
$sel:uniformBufferStandardLayout:PhysicalDeviceVulkan12Features :: PhysicalDeviceVulkan12Features -> Bool
$sel:imagelessFramebuffer:PhysicalDeviceVulkan12Features :: PhysicalDeviceVulkan12Features -> Bool
$sel:scalarBlockLayout:PhysicalDeviceVulkan12Features :: PhysicalDeviceVulkan12Features -> Bool
$sel:samplerFilterMinmax:PhysicalDeviceVulkan12Features :: PhysicalDeviceVulkan12Features -> Bool
$sel:runtimeDescriptorArray:PhysicalDeviceVulkan12Features :: PhysicalDeviceVulkan12Features -> Bool
$sel:descriptorBindingVariableDescriptorCount:PhysicalDeviceVulkan12Features :: PhysicalDeviceVulkan12Features -> Bool
$sel:descriptorBindingPartiallyBound:PhysicalDeviceVulkan12Features :: PhysicalDeviceVulkan12Features -> Bool
$sel:descriptorBindingUpdateUnusedWhilePending:PhysicalDeviceVulkan12Features :: PhysicalDeviceVulkan12Features -> Bool
$sel:descriptorBindingStorageTexelBufferUpdateAfterBind:PhysicalDeviceVulkan12Features :: PhysicalDeviceVulkan12Features -> Bool
$sel:descriptorBindingUniformTexelBufferUpdateAfterBind:PhysicalDeviceVulkan12Features :: PhysicalDeviceVulkan12Features -> Bool
$sel:descriptorBindingStorageBufferUpdateAfterBind:PhysicalDeviceVulkan12Features :: PhysicalDeviceVulkan12Features -> Bool
$sel:descriptorBindingStorageImageUpdateAfterBind:PhysicalDeviceVulkan12Features :: PhysicalDeviceVulkan12Features -> Bool
$sel:descriptorBindingSampledImageUpdateAfterBind:PhysicalDeviceVulkan12Features :: PhysicalDeviceVulkan12Features -> Bool
$sel:descriptorBindingUniformBufferUpdateAfterBind:PhysicalDeviceVulkan12Features :: PhysicalDeviceVulkan12Features -> Bool
$sel:shaderStorageTexelBufferArrayNonUniformIndexing:PhysicalDeviceVulkan12Features :: PhysicalDeviceVulkan12Features -> Bool
$sel:shaderUniformTexelBufferArrayNonUniformIndexing:PhysicalDeviceVulkan12Features :: PhysicalDeviceVulkan12Features -> Bool
$sel:shaderInputAttachmentArrayNonUniformIndexing:PhysicalDeviceVulkan12Features :: PhysicalDeviceVulkan12Features -> Bool
$sel:shaderStorageImageArrayNonUniformIndexing:PhysicalDeviceVulkan12Features :: PhysicalDeviceVulkan12Features -> Bool
$sel:shaderStorageBufferArrayNonUniformIndexing:PhysicalDeviceVulkan12Features :: PhysicalDeviceVulkan12Features -> Bool
$sel:shaderSampledImageArrayNonUniformIndexing:PhysicalDeviceVulkan12Features :: PhysicalDeviceVulkan12Features -> Bool
$sel:shaderUniformBufferArrayNonUniformIndexing:PhysicalDeviceVulkan12Features :: PhysicalDeviceVulkan12Features -> Bool
$sel:shaderStorageTexelBufferArrayDynamicIndexing:PhysicalDeviceVulkan12Features :: PhysicalDeviceVulkan12Features -> Bool
$sel:shaderUniformTexelBufferArrayDynamicIndexing:PhysicalDeviceVulkan12Features :: PhysicalDeviceVulkan12Features -> Bool
$sel:shaderInputAttachmentArrayDynamicIndexing:PhysicalDeviceVulkan12Features :: PhysicalDeviceVulkan12Features -> Bool
$sel:descriptorIndexing:PhysicalDeviceVulkan12Features :: PhysicalDeviceVulkan12Features -> Bool
$sel:shaderInt8:PhysicalDeviceVulkan12Features :: PhysicalDeviceVulkan12Features -> Bool
$sel:shaderFloat16:PhysicalDeviceVulkan12Features :: PhysicalDeviceVulkan12Features -> Bool
$sel:shaderSharedInt64Atomics:PhysicalDeviceVulkan12Features :: PhysicalDeviceVulkan12Features -> Bool
$sel:shaderBufferInt64Atomics:PhysicalDeviceVulkan12Features :: PhysicalDeviceVulkan12Features -> Bool
$sel:storagePushConstant8:PhysicalDeviceVulkan12Features :: PhysicalDeviceVulkan12Features -> Bool
$sel:uniformAndStorageBuffer8BitAccess:PhysicalDeviceVulkan12Features :: PhysicalDeviceVulkan12Features -> Bool
$sel:storageBuffer8BitAccess:PhysicalDeviceVulkan12Features :: PhysicalDeviceVulkan12Features -> Bool
$sel:drawIndirectCount:PhysicalDeviceVulkan12Features :: PhysicalDeviceVulkan12Features -> Bool
$sel:samplerMirrorClampToEdge:PhysicalDeviceVulkan12Features :: PhysicalDeviceVulkan12Features -> Bool
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_VULKAN_1_2_FEATURES)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
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 PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
samplerMirrorClampToEdge))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
drawIndirectCount))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
storageBuffer8BitAccess))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
uniformAndStorageBuffer8BitAccess))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
storagePushConstant8))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
36 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderBufferInt64Atomics))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderSharedInt64Atomics))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
44 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderFloat16))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderInt8))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
52 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
descriptorIndexing))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderInputAttachmentArrayDynamicIndexing))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
60 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderUniformTexelBufferArrayDynamicIndexing))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
64 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderStorageTexelBufferArrayDynamicIndexing))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
68 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderUniformBufferArrayNonUniformIndexing))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
72 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderSampledImageArrayNonUniformIndexing))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
76 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderStorageBufferArrayNonUniformIndexing))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
80 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderStorageImageArrayNonUniformIndexing))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
84 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderInputAttachmentArrayNonUniformIndexing))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
88 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderUniformTexelBufferArrayNonUniformIndexing))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
92 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderStorageTexelBufferArrayNonUniformIndexing))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
96 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
descriptorBindingUniformBufferUpdateAfterBind))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
100 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
descriptorBindingSampledImageUpdateAfterBind))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
104 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
descriptorBindingStorageImageUpdateAfterBind))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
108 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
descriptorBindingStorageBufferUpdateAfterBind))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
112 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
descriptorBindingUniformTexelBufferUpdateAfterBind))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
116 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
descriptorBindingStorageTexelBufferUpdateAfterBind))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
120 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
descriptorBindingUpdateUnusedWhilePending))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
124 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
descriptorBindingPartiallyBound))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
128 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
descriptorBindingVariableDescriptorCount))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
132 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
runtimeDescriptorArray))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
136 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
samplerFilterMinmax))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
140 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
scalarBlockLayout))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
144 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
imagelessFramebuffer))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
148 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
uniformBufferStandardLayout))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
152 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderSubgroupExtendedTypes))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
156 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
separateDepthStencilLayouts))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
160 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
hostQueryReset))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
164 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
timelineSemaphore))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
168 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
bufferDeviceAddress))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
172 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
bufferDeviceAddressCaptureReplay))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
176 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
bufferDeviceAddressMultiDevice))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
180 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
vulkanMemoryModel))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
184 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
vulkanMemoryModelDeviceScope))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
188 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
vulkanMemoryModelAvailabilityVisibilityChains))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
192 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderOutputViewportIndex))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
196 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderOutputLayer))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
200 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
subgroupBroadcastDynamicId))
IO b
f
cStructSize :: Int
cStructSize = Int
208
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b. Ptr PhysicalDeviceVulkan12Features -> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceVulkan12Features
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_VULKAN_1_2_FEATURES)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
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 PhysicalDeviceVulkan12Features
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 PhysicalDeviceVulkan12Features
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 PhysicalDeviceVulkan12Features
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 PhysicalDeviceVulkan12Features
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 PhysicalDeviceVulkan12Features
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 PhysicalDeviceVulkan12Features
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 PhysicalDeviceVulkan12Features
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 PhysicalDeviceVulkan12Features
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 PhysicalDeviceVulkan12Features
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 PhysicalDeviceVulkan12Features
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 PhysicalDeviceVulkan12Features
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 PhysicalDeviceVulkan12Features
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 PhysicalDeviceVulkan12Features
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 PhysicalDeviceVulkan12Features
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 PhysicalDeviceVulkan12Features
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 PhysicalDeviceVulkan12Features
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 PhysicalDeviceVulkan12Features
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 PhysicalDeviceVulkan12Features
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 PhysicalDeviceVulkan12Features
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 PhysicalDeviceVulkan12Features
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 PhysicalDeviceVulkan12Features
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 PhysicalDeviceVulkan12Features
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 PhysicalDeviceVulkan12Features
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 PhysicalDeviceVulkan12Features
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 PhysicalDeviceVulkan12Features
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 PhysicalDeviceVulkan12Features
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 PhysicalDeviceVulkan12Features
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 PhysicalDeviceVulkan12Features
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 PhysicalDeviceVulkan12Features
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 PhysicalDeviceVulkan12Features
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 PhysicalDeviceVulkan12Features
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 PhysicalDeviceVulkan12Features
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 PhysicalDeviceVulkan12Features
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 PhysicalDeviceVulkan12Features
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 PhysicalDeviceVulkan12Features
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 PhysicalDeviceVulkan12Features
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 PhysicalDeviceVulkan12Features
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 PhysicalDeviceVulkan12Features
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 PhysicalDeviceVulkan12Features
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 PhysicalDeviceVulkan12Features
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 PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
176 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
180 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
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 PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
188 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
192 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
196 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
200 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
IO b
f
instance FromCStruct PhysicalDeviceVulkan12Features where
peekCStruct :: Ptr PhysicalDeviceVulkan12Features
-> IO PhysicalDeviceVulkan12Features
peekCStruct Ptr PhysicalDeviceVulkan12Features
p = do
Bool32
samplerMirrorClampToEdge <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32))
Bool32
drawIndirectCount <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32))
Bool32
storageBuffer8BitAccess <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Bool32))
Bool32
uniformAndStorageBuffer8BitAccess <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr Bool32))
Bool32
storagePushConstant8 <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr Bool32))
Bool32
shaderBufferInt64Atomics <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
36 :: Ptr Bool32))
Bool32
shaderSharedInt64Atomics <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr Bool32))
Bool32
shaderFloat16 <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
44 :: Ptr Bool32))
Bool32
shaderInt8 <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48 :: Ptr Bool32))
Bool32
descriptorIndexing <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
52 :: Ptr Bool32))
Bool32
shaderInputAttachmentArrayDynamicIndexing <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56 :: Ptr Bool32))
Bool32
shaderUniformTexelBufferArrayDynamicIndexing <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
60 :: Ptr Bool32))
Bool32
shaderStorageTexelBufferArrayDynamicIndexing <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
64 :: Ptr Bool32))
Bool32
shaderUniformBufferArrayNonUniformIndexing <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
68 :: Ptr Bool32))
Bool32
shaderSampledImageArrayNonUniformIndexing <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
72 :: Ptr Bool32))
Bool32
shaderStorageBufferArrayNonUniformIndexing <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
76 :: Ptr Bool32))
Bool32
shaderStorageImageArrayNonUniformIndexing <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
80 :: Ptr Bool32))
Bool32
shaderInputAttachmentArrayNonUniformIndexing <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
84 :: Ptr Bool32))
Bool32
shaderUniformTexelBufferArrayNonUniformIndexing <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
88 :: Ptr Bool32))
Bool32
shaderStorageTexelBufferArrayNonUniformIndexing <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
92 :: Ptr Bool32))
Bool32
descriptorBindingUniformBufferUpdateAfterBind <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
96 :: Ptr Bool32))
Bool32
descriptorBindingSampledImageUpdateAfterBind <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
100 :: Ptr Bool32))
Bool32
descriptorBindingStorageImageUpdateAfterBind <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
104 :: Ptr Bool32))
Bool32
descriptorBindingStorageBufferUpdateAfterBind <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
108 :: Ptr Bool32))
Bool32
descriptorBindingUniformTexelBufferUpdateAfterBind <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
112 :: Ptr Bool32))
Bool32
descriptorBindingStorageTexelBufferUpdateAfterBind <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
116 :: Ptr Bool32))
Bool32
descriptorBindingUpdateUnusedWhilePending <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
120 :: Ptr Bool32))
Bool32
descriptorBindingPartiallyBound <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
124 :: Ptr Bool32))
Bool32
descriptorBindingVariableDescriptorCount <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
128 :: Ptr Bool32))
Bool32
runtimeDescriptorArray <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
132 :: Ptr Bool32))
Bool32
samplerFilterMinmax <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
136 :: Ptr Bool32))
Bool32
scalarBlockLayout <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
140 :: Ptr Bool32))
Bool32
imagelessFramebuffer <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
144 :: Ptr Bool32))
Bool32
uniformBufferStandardLayout <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
148 :: Ptr Bool32))
Bool32
shaderSubgroupExtendedTypes <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
152 :: Ptr Bool32))
Bool32
separateDepthStencilLayouts <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
156 :: Ptr Bool32))
Bool32
hostQueryReset <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
160 :: Ptr Bool32))
Bool32
timelineSemaphore <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
164 :: Ptr Bool32))
Bool32
bufferDeviceAddress <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
168 :: Ptr Bool32))
Bool32
bufferDeviceAddressCaptureReplay <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
172 :: Ptr Bool32))
Bool32
bufferDeviceAddressMultiDevice <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
176 :: Ptr Bool32))
Bool32
vulkanMemoryModel <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
180 :: Ptr Bool32))
Bool32
vulkanMemoryModelDeviceScope <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
184 :: Ptr Bool32))
Bool32
vulkanMemoryModelAvailabilityVisibilityChains <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
188 :: Ptr Bool32))
Bool32
shaderOutputViewportIndex <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
192 :: Ptr Bool32))
Bool32
shaderOutputLayer <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
196 :: Ptr Bool32))
Bool32
subgroupBroadcastDynamicId <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
200 :: 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
-> 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
-> Bool
-> Bool
-> PhysicalDeviceVulkan12Features
PhysicalDeviceVulkan12Features
(Bool32 -> Bool
bool32ToBool Bool32
samplerMirrorClampToEdge)
(Bool32 -> Bool
bool32ToBool Bool32
drawIndirectCount)
(Bool32 -> Bool
bool32ToBool Bool32
storageBuffer8BitAccess)
(Bool32 -> Bool
bool32ToBool Bool32
uniformAndStorageBuffer8BitAccess)
(Bool32 -> Bool
bool32ToBool Bool32
storagePushConstant8)
(Bool32 -> Bool
bool32ToBool Bool32
shaderBufferInt64Atomics)
(Bool32 -> Bool
bool32ToBool Bool32
shaderSharedInt64Atomics)
(Bool32 -> Bool
bool32ToBool Bool32
shaderFloat16)
(Bool32 -> Bool
bool32ToBool Bool32
shaderInt8)
(Bool32 -> Bool
bool32ToBool Bool32
descriptorIndexing)
(Bool32 -> Bool
bool32ToBool Bool32
shaderInputAttachmentArrayDynamicIndexing)
(Bool32 -> Bool
bool32ToBool Bool32
shaderUniformTexelBufferArrayDynamicIndexing)
(Bool32 -> Bool
bool32ToBool Bool32
shaderStorageTexelBufferArrayDynamicIndexing)
(Bool32 -> Bool
bool32ToBool Bool32
shaderUniformBufferArrayNonUniformIndexing)
(Bool32 -> Bool
bool32ToBool Bool32
shaderSampledImageArrayNonUniformIndexing)
(Bool32 -> Bool
bool32ToBool Bool32
shaderStorageBufferArrayNonUniformIndexing)
(Bool32 -> Bool
bool32ToBool Bool32
shaderStorageImageArrayNonUniformIndexing)
(Bool32 -> Bool
bool32ToBool Bool32
shaderInputAttachmentArrayNonUniformIndexing)
(Bool32 -> Bool
bool32ToBool Bool32
shaderUniformTexelBufferArrayNonUniformIndexing)
(Bool32 -> Bool
bool32ToBool Bool32
shaderStorageTexelBufferArrayNonUniformIndexing)
(Bool32 -> Bool
bool32ToBool Bool32
descriptorBindingUniformBufferUpdateAfterBind)
(Bool32 -> Bool
bool32ToBool Bool32
descriptorBindingSampledImageUpdateAfterBind)
(Bool32 -> Bool
bool32ToBool Bool32
descriptorBindingStorageImageUpdateAfterBind)
(Bool32 -> Bool
bool32ToBool Bool32
descriptorBindingStorageBufferUpdateAfterBind)
(Bool32 -> Bool
bool32ToBool Bool32
descriptorBindingUniformTexelBufferUpdateAfterBind)
(Bool32 -> Bool
bool32ToBool Bool32
descriptorBindingStorageTexelBufferUpdateAfterBind)
(Bool32 -> Bool
bool32ToBool Bool32
descriptorBindingUpdateUnusedWhilePending)
(Bool32 -> Bool
bool32ToBool Bool32
descriptorBindingPartiallyBound)
(Bool32 -> Bool
bool32ToBool Bool32
descriptorBindingVariableDescriptorCount)
(Bool32 -> Bool
bool32ToBool Bool32
runtimeDescriptorArray)
(Bool32 -> Bool
bool32ToBool Bool32
samplerFilterMinmax)
(Bool32 -> Bool
bool32ToBool Bool32
scalarBlockLayout)
(Bool32 -> Bool
bool32ToBool Bool32
imagelessFramebuffer)
(Bool32 -> Bool
bool32ToBool Bool32
uniformBufferStandardLayout)
(Bool32 -> Bool
bool32ToBool Bool32
shaderSubgroupExtendedTypes)
(Bool32 -> Bool
bool32ToBool Bool32
separateDepthStencilLayouts)
(Bool32 -> Bool
bool32ToBool Bool32
hostQueryReset)
(Bool32 -> Bool
bool32ToBool Bool32
timelineSemaphore)
(Bool32 -> Bool
bool32ToBool Bool32
bufferDeviceAddress)
(Bool32 -> Bool
bool32ToBool Bool32
bufferDeviceAddressCaptureReplay)
(Bool32 -> Bool
bool32ToBool Bool32
bufferDeviceAddressMultiDevice)
(Bool32 -> Bool
bool32ToBool Bool32
vulkanMemoryModel)
(Bool32 -> Bool
bool32ToBool Bool32
vulkanMemoryModelDeviceScope)
(Bool32 -> Bool
bool32ToBool Bool32
vulkanMemoryModelAvailabilityVisibilityChains)
(Bool32 -> Bool
bool32ToBool Bool32
shaderOutputViewportIndex)
(Bool32 -> Bool
bool32ToBool Bool32
shaderOutputLayer)
(Bool32 -> Bool
bool32ToBool Bool32
subgroupBroadcastDynamicId)
instance Storable PhysicalDeviceVulkan12Features where
sizeOf :: PhysicalDeviceVulkan12Features -> Int
sizeOf ~PhysicalDeviceVulkan12Features
_ = Int
208
alignment :: PhysicalDeviceVulkan12Features -> Int
alignment ~PhysicalDeviceVulkan12Features
_ = Int
8
peek :: Ptr PhysicalDeviceVulkan12Features
-> IO PhysicalDeviceVulkan12Features
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr PhysicalDeviceVulkan12Features
-> PhysicalDeviceVulkan12Features -> IO ()
poke Ptr PhysicalDeviceVulkan12Features
ptr PhysicalDeviceVulkan12Features
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceVulkan12Features
ptr PhysicalDeviceVulkan12Features
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PhysicalDeviceVulkan12Features where
zero :: PhysicalDeviceVulkan12Features
zero = 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
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> PhysicalDeviceVulkan12Features
PhysicalDeviceVulkan12Features
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
forall a. Zero a => a
zero
forall a. Zero a => a
zero
data PhysicalDeviceVulkan12Properties = PhysicalDeviceVulkan12Properties
{
PhysicalDeviceVulkan12Properties -> DriverId
driverID :: DriverId
,
PhysicalDeviceVulkan12Properties -> ByteString
driverName :: ByteString
,
PhysicalDeviceVulkan12Properties -> ByteString
driverInfo :: ByteString
,
PhysicalDeviceVulkan12Properties -> ConformanceVersion
conformanceVersion :: ConformanceVersion
,
PhysicalDeviceVulkan12Properties -> ShaderFloatControlsIndependence
denormBehaviorIndependence :: ShaderFloatControlsIndependence
,
PhysicalDeviceVulkan12Properties -> ShaderFloatControlsIndependence
roundingModeIndependence :: ShaderFloatControlsIndependence
,
PhysicalDeviceVulkan12Properties -> Bool
shaderSignedZeroInfNanPreserveFloat16 :: Bool
,
PhysicalDeviceVulkan12Properties -> Bool
shaderSignedZeroInfNanPreserveFloat32 :: Bool
,
PhysicalDeviceVulkan12Properties -> Bool
shaderSignedZeroInfNanPreserveFloat64 :: Bool
,
PhysicalDeviceVulkan12Properties -> Bool
shaderDenormPreserveFloat16 :: Bool
,
PhysicalDeviceVulkan12Properties -> Bool
shaderDenormPreserveFloat32 :: Bool
,
PhysicalDeviceVulkan12Properties -> Bool
shaderDenormPreserveFloat64 :: Bool
,
PhysicalDeviceVulkan12Properties -> Bool
shaderDenormFlushToZeroFloat16 :: Bool
,
PhysicalDeviceVulkan12Properties -> Bool
shaderDenormFlushToZeroFloat32 :: Bool
,
PhysicalDeviceVulkan12Properties -> Bool
shaderDenormFlushToZeroFloat64 :: Bool
,
PhysicalDeviceVulkan12Properties -> Bool
shaderRoundingModeRTEFloat16 :: Bool
,
PhysicalDeviceVulkan12Properties -> Bool
shaderRoundingModeRTEFloat32 :: Bool
,
PhysicalDeviceVulkan12Properties -> Bool
shaderRoundingModeRTEFloat64 :: Bool
,
PhysicalDeviceVulkan12Properties -> Bool
shaderRoundingModeRTZFloat16 :: Bool
,
PhysicalDeviceVulkan12Properties -> Bool
shaderRoundingModeRTZFloat32 :: Bool
,
PhysicalDeviceVulkan12Properties -> Bool
shaderRoundingModeRTZFloat64 :: Bool
,
PhysicalDeviceVulkan12Properties -> Word32
maxUpdateAfterBindDescriptorsInAllPools :: Word32
,
PhysicalDeviceVulkan12Properties -> Bool
shaderUniformBufferArrayNonUniformIndexingNative :: Bool
,
PhysicalDeviceVulkan12Properties -> Bool
shaderSampledImageArrayNonUniformIndexingNative :: Bool
,
PhysicalDeviceVulkan12Properties -> Bool
shaderStorageBufferArrayNonUniformIndexingNative :: Bool
,
PhysicalDeviceVulkan12Properties -> Bool
shaderStorageImageArrayNonUniformIndexingNative :: Bool
,
PhysicalDeviceVulkan12Properties -> Bool
shaderInputAttachmentArrayNonUniformIndexingNative :: Bool
,
PhysicalDeviceVulkan12Properties -> Bool
robustBufferAccessUpdateAfterBind :: Bool
,
PhysicalDeviceVulkan12Properties -> Bool
quadDivergentImplicitLod :: Bool
,
PhysicalDeviceVulkan12Properties -> Word32
maxPerStageDescriptorUpdateAfterBindSamplers :: Word32
,
PhysicalDeviceVulkan12Properties -> Word32
maxPerStageDescriptorUpdateAfterBindUniformBuffers :: Word32
,
PhysicalDeviceVulkan12Properties -> Word32
maxPerStageDescriptorUpdateAfterBindStorageBuffers :: Word32
,
PhysicalDeviceVulkan12Properties -> Word32
maxPerStageDescriptorUpdateAfterBindSampledImages :: Word32
,
PhysicalDeviceVulkan12Properties -> Word32
maxPerStageDescriptorUpdateAfterBindStorageImages :: Word32
,
PhysicalDeviceVulkan12Properties -> Word32
maxPerStageDescriptorUpdateAfterBindInputAttachments :: Word32
,
PhysicalDeviceVulkan12Properties -> Word32
maxPerStageUpdateAfterBindResources :: Word32
,
PhysicalDeviceVulkan12Properties -> Word32
maxDescriptorSetUpdateAfterBindSamplers :: Word32
,
PhysicalDeviceVulkan12Properties -> Word32
maxDescriptorSetUpdateAfterBindUniformBuffers :: Word32
,
PhysicalDeviceVulkan12Properties -> Word32
maxDescriptorSetUpdateAfterBindUniformBuffersDynamic :: Word32
,
PhysicalDeviceVulkan12Properties -> Word32
maxDescriptorSetUpdateAfterBindStorageBuffers :: Word32
,
PhysicalDeviceVulkan12Properties -> Word32
maxDescriptorSetUpdateAfterBindStorageBuffersDynamic :: Word32
,
PhysicalDeviceVulkan12Properties -> Word32
maxDescriptorSetUpdateAfterBindSampledImages :: Word32
,
PhysicalDeviceVulkan12Properties -> Word32
maxDescriptorSetUpdateAfterBindStorageImages :: Word32
,
PhysicalDeviceVulkan12Properties -> Word32
maxDescriptorSetUpdateAfterBindInputAttachments :: Word32
,
PhysicalDeviceVulkan12Properties -> ResolveModeFlags
supportedDepthResolveModes :: ResolveModeFlags
,
PhysicalDeviceVulkan12Properties -> ResolveModeFlags
supportedStencilResolveModes :: ResolveModeFlags
,
PhysicalDeviceVulkan12Properties -> Bool
independentResolveNone :: Bool
,
PhysicalDeviceVulkan12Properties -> Bool
independentResolve :: Bool
,
PhysicalDeviceVulkan12Properties -> Bool
filterMinmaxSingleComponentFormats :: Bool
,
PhysicalDeviceVulkan12Properties -> Bool
filterMinmaxImageComponentMapping :: Bool
,
PhysicalDeviceVulkan12Properties -> DeviceSize
maxTimelineSemaphoreValueDifference :: Word64
,
PhysicalDeviceVulkan12Properties -> SampleCountFlags
framebufferIntegerColorSampleCounts :: SampleCountFlags
}
deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceVulkan12Properties)
#endif
deriving instance Show PhysicalDeviceVulkan12Properties
instance ToCStruct PhysicalDeviceVulkan12Properties where
withCStruct :: forall b.
PhysicalDeviceVulkan12Properties
-> (Ptr PhysicalDeviceVulkan12Properties -> IO b) -> IO b
withCStruct PhysicalDeviceVulkan12Properties
x Ptr PhysicalDeviceVulkan12Properties -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
736 forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceVulkan12Properties
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceVulkan12Properties
p PhysicalDeviceVulkan12Properties
x (Ptr PhysicalDeviceVulkan12Properties -> IO b
f Ptr PhysicalDeviceVulkan12Properties
p)
pokeCStruct :: forall b.
Ptr PhysicalDeviceVulkan12Properties
-> PhysicalDeviceVulkan12Properties -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceVulkan12Properties
p PhysicalDeviceVulkan12Properties{Bool
Word32
DeviceSize
ByteString
SampleCountFlags
ConformanceVersion
ShaderFloatControlsIndependence
DriverId
ResolveModeFlags
framebufferIntegerColorSampleCounts :: SampleCountFlags
maxTimelineSemaphoreValueDifference :: DeviceSize
filterMinmaxImageComponentMapping :: Bool
filterMinmaxSingleComponentFormats :: Bool
independentResolve :: Bool
independentResolveNone :: Bool
supportedStencilResolveModes :: ResolveModeFlags
supportedDepthResolveModes :: ResolveModeFlags
maxDescriptorSetUpdateAfterBindInputAttachments :: Word32
maxDescriptorSetUpdateAfterBindStorageImages :: Word32
maxDescriptorSetUpdateAfterBindSampledImages :: Word32
maxDescriptorSetUpdateAfterBindStorageBuffersDynamic :: Word32
maxDescriptorSetUpdateAfterBindStorageBuffers :: Word32
maxDescriptorSetUpdateAfterBindUniformBuffersDynamic :: Word32
maxDescriptorSetUpdateAfterBindUniformBuffers :: Word32
maxDescriptorSetUpdateAfterBindSamplers :: Word32
maxPerStageUpdateAfterBindResources :: Word32
maxPerStageDescriptorUpdateAfterBindInputAttachments :: Word32
maxPerStageDescriptorUpdateAfterBindStorageImages :: Word32
maxPerStageDescriptorUpdateAfterBindSampledImages :: Word32
maxPerStageDescriptorUpdateAfterBindStorageBuffers :: Word32
maxPerStageDescriptorUpdateAfterBindUniformBuffers :: Word32
maxPerStageDescriptorUpdateAfterBindSamplers :: Word32
quadDivergentImplicitLod :: Bool
robustBufferAccessUpdateAfterBind :: Bool
shaderInputAttachmentArrayNonUniformIndexingNative :: Bool
shaderStorageImageArrayNonUniformIndexingNative :: Bool
shaderStorageBufferArrayNonUniformIndexingNative :: Bool
shaderSampledImageArrayNonUniformIndexingNative :: Bool
shaderUniformBufferArrayNonUniformIndexingNative :: Bool
maxUpdateAfterBindDescriptorsInAllPools :: Word32
shaderRoundingModeRTZFloat64 :: Bool
shaderRoundingModeRTZFloat32 :: Bool
shaderRoundingModeRTZFloat16 :: Bool
shaderRoundingModeRTEFloat64 :: Bool
shaderRoundingModeRTEFloat32 :: Bool
shaderRoundingModeRTEFloat16 :: Bool
shaderDenormFlushToZeroFloat64 :: Bool
shaderDenormFlushToZeroFloat32 :: Bool
shaderDenormFlushToZeroFloat16 :: Bool
shaderDenormPreserveFloat64 :: Bool
shaderDenormPreserveFloat32 :: Bool
shaderDenormPreserveFloat16 :: Bool
shaderSignedZeroInfNanPreserveFloat64 :: Bool
shaderSignedZeroInfNanPreserveFloat32 :: Bool
shaderSignedZeroInfNanPreserveFloat16 :: Bool
roundingModeIndependence :: ShaderFloatControlsIndependence
denormBehaviorIndependence :: ShaderFloatControlsIndependence
conformanceVersion :: ConformanceVersion
driverInfo :: ByteString
driverName :: ByteString
driverID :: DriverId
$sel:framebufferIntegerColorSampleCounts:PhysicalDeviceVulkan12Properties :: PhysicalDeviceVulkan12Properties -> SampleCountFlags
$sel:maxTimelineSemaphoreValueDifference:PhysicalDeviceVulkan12Properties :: PhysicalDeviceVulkan12Properties -> DeviceSize
$sel:filterMinmaxImageComponentMapping:PhysicalDeviceVulkan12Properties :: PhysicalDeviceVulkan12Properties -> Bool
$sel:filterMinmaxSingleComponentFormats:PhysicalDeviceVulkan12Properties :: PhysicalDeviceVulkan12Properties -> Bool
$sel:independentResolve:PhysicalDeviceVulkan12Properties :: PhysicalDeviceVulkan12Properties -> Bool
$sel:independentResolveNone:PhysicalDeviceVulkan12Properties :: PhysicalDeviceVulkan12Properties -> Bool
$sel:supportedStencilResolveModes:PhysicalDeviceVulkan12Properties :: PhysicalDeviceVulkan12Properties -> ResolveModeFlags
$sel:supportedDepthResolveModes:PhysicalDeviceVulkan12Properties :: PhysicalDeviceVulkan12Properties -> ResolveModeFlags
$sel:maxDescriptorSetUpdateAfterBindInputAttachments:PhysicalDeviceVulkan12Properties :: PhysicalDeviceVulkan12Properties -> Word32
$sel:maxDescriptorSetUpdateAfterBindStorageImages:PhysicalDeviceVulkan12Properties :: PhysicalDeviceVulkan12Properties -> Word32
$sel:maxDescriptorSetUpdateAfterBindSampledImages:PhysicalDeviceVulkan12Properties :: PhysicalDeviceVulkan12Properties -> Word32
$sel:maxDescriptorSetUpdateAfterBindStorageBuffersDynamic:PhysicalDeviceVulkan12Properties :: PhysicalDeviceVulkan12Properties -> Word32
$sel:maxDescriptorSetUpdateAfterBindStorageBuffers:PhysicalDeviceVulkan12Properties :: PhysicalDeviceVulkan12Properties -> Word32
$sel:maxDescriptorSetUpdateAfterBindUniformBuffersDynamic:PhysicalDeviceVulkan12Properties :: PhysicalDeviceVulkan12Properties -> Word32
$sel:maxDescriptorSetUpdateAfterBindUniformBuffers:PhysicalDeviceVulkan12Properties :: PhysicalDeviceVulkan12Properties -> Word32
$sel:maxDescriptorSetUpdateAfterBindSamplers:PhysicalDeviceVulkan12Properties :: PhysicalDeviceVulkan12Properties -> Word32
$sel:maxPerStageUpdateAfterBindResources:PhysicalDeviceVulkan12Properties :: PhysicalDeviceVulkan12Properties -> Word32
$sel:maxPerStageDescriptorUpdateAfterBindInputAttachments:PhysicalDeviceVulkan12Properties :: PhysicalDeviceVulkan12Properties -> Word32
$sel:maxPerStageDescriptorUpdateAfterBindStorageImages:PhysicalDeviceVulkan12Properties :: PhysicalDeviceVulkan12Properties -> Word32
$sel:maxPerStageDescriptorUpdateAfterBindSampledImages:PhysicalDeviceVulkan12Properties :: PhysicalDeviceVulkan12Properties -> Word32
$sel:maxPerStageDescriptorUpdateAfterBindStorageBuffers:PhysicalDeviceVulkan12Properties :: PhysicalDeviceVulkan12Properties -> Word32
$sel:maxPerStageDescriptorUpdateAfterBindUniformBuffers:PhysicalDeviceVulkan12Properties :: PhysicalDeviceVulkan12Properties -> Word32
$sel:maxPerStageDescriptorUpdateAfterBindSamplers:PhysicalDeviceVulkan12Properties :: PhysicalDeviceVulkan12Properties -> Word32
$sel:quadDivergentImplicitLod:PhysicalDeviceVulkan12Properties :: PhysicalDeviceVulkan12Properties -> Bool
$sel:robustBufferAccessUpdateAfterBind:PhysicalDeviceVulkan12Properties :: PhysicalDeviceVulkan12Properties -> Bool
$sel:shaderInputAttachmentArrayNonUniformIndexingNative:PhysicalDeviceVulkan12Properties :: PhysicalDeviceVulkan12Properties -> Bool
$sel:shaderStorageImageArrayNonUniformIndexingNative:PhysicalDeviceVulkan12Properties :: PhysicalDeviceVulkan12Properties -> Bool
$sel:shaderStorageBufferArrayNonUniformIndexingNative:PhysicalDeviceVulkan12Properties :: PhysicalDeviceVulkan12Properties -> Bool
$sel:shaderSampledImageArrayNonUniformIndexingNative:PhysicalDeviceVulkan12Properties :: PhysicalDeviceVulkan12Properties -> Bool
$sel:shaderUniformBufferArrayNonUniformIndexingNative:PhysicalDeviceVulkan12Properties :: PhysicalDeviceVulkan12Properties -> Bool
$sel:maxUpdateAfterBindDescriptorsInAllPools:PhysicalDeviceVulkan12Properties :: PhysicalDeviceVulkan12Properties -> Word32
$sel:shaderRoundingModeRTZFloat64:PhysicalDeviceVulkan12Properties :: PhysicalDeviceVulkan12Properties -> Bool
$sel:shaderRoundingModeRTZFloat32:PhysicalDeviceVulkan12Properties :: PhysicalDeviceVulkan12Properties -> Bool
$sel:shaderRoundingModeRTZFloat16:PhysicalDeviceVulkan12Properties :: PhysicalDeviceVulkan12Properties -> Bool
$sel:shaderRoundingModeRTEFloat64:PhysicalDeviceVulkan12Properties :: PhysicalDeviceVulkan12Properties -> Bool
$sel:shaderRoundingModeRTEFloat32:PhysicalDeviceVulkan12Properties :: PhysicalDeviceVulkan12Properties -> Bool
$sel:shaderRoundingModeRTEFloat16:PhysicalDeviceVulkan12Properties :: PhysicalDeviceVulkan12Properties -> Bool
$sel:shaderDenormFlushToZeroFloat64:PhysicalDeviceVulkan12Properties :: PhysicalDeviceVulkan12Properties -> Bool
$sel:shaderDenormFlushToZeroFloat32:PhysicalDeviceVulkan12Properties :: PhysicalDeviceVulkan12Properties -> Bool
$sel:shaderDenormFlushToZeroFloat16:PhysicalDeviceVulkan12Properties :: PhysicalDeviceVulkan12Properties -> Bool
$sel:shaderDenormPreserveFloat64:PhysicalDeviceVulkan12Properties :: PhysicalDeviceVulkan12Properties -> Bool
$sel:shaderDenormPreserveFloat32:PhysicalDeviceVulkan12Properties :: PhysicalDeviceVulkan12Properties -> Bool
$sel:shaderDenormPreserveFloat16:PhysicalDeviceVulkan12Properties :: PhysicalDeviceVulkan12Properties -> Bool
$sel:shaderSignedZeroInfNanPreserveFloat64:PhysicalDeviceVulkan12Properties :: PhysicalDeviceVulkan12Properties -> Bool
$sel:shaderSignedZeroInfNanPreserveFloat32:PhysicalDeviceVulkan12Properties :: PhysicalDeviceVulkan12Properties -> Bool
$sel:shaderSignedZeroInfNanPreserveFloat16:PhysicalDeviceVulkan12Properties :: PhysicalDeviceVulkan12Properties -> Bool
$sel:roundingModeIndependence:PhysicalDeviceVulkan12Properties :: PhysicalDeviceVulkan12Properties -> ShaderFloatControlsIndependence
$sel:denormBehaviorIndependence:PhysicalDeviceVulkan12Properties :: PhysicalDeviceVulkan12Properties -> ShaderFloatControlsIndependence
$sel:conformanceVersion:PhysicalDeviceVulkan12Properties :: PhysicalDeviceVulkan12Properties -> ConformanceVersion
$sel:driverInfo:PhysicalDeviceVulkan12Properties :: PhysicalDeviceVulkan12Properties -> ByteString
$sel:driverName:PhysicalDeviceVulkan12Properties :: PhysicalDeviceVulkan12Properties -> ByteString
$sel:driverID:PhysicalDeviceVulkan12Properties :: PhysicalDeviceVulkan12Properties -> DriverId
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_VULKAN_1_2_PROPERTIES)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
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 PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DriverId)) (DriverId
driverID)
forall (n :: Nat).
KnownNat n =>
Ptr (FixedArray n CChar) -> ByteString -> IO ()
pokeFixedLengthNullTerminatedByteString ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr (FixedArray MAX_DRIVER_NAME_SIZE CChar))) (ByteString
driverName)
forall (n :: Nat).
KnownNat n =>
Ptr (FixedArray n CChar) -> ByteString -> IO ()
pokeFixedLengthNullTerminatedByteString ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
276 :: Ptr (FixedArray MAX_DRIVER_INFO_SIZE CChar))) (ByteString
driverInfo)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
532 :: Ptr ConformanceVersion)) (ConformanceVersion
conformanceVersion)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
536 :: Ptr ShaderFloatControlsIndependence)) (ShaderFloatControlsIndependence
denormBehaviorIndependence)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
540 :: Ptr ShaderFloatControlsIndependence)) (ShaderFloatControlsIndependence
roundingModeIndependence)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
544 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderSignedZeroInfNanPreserveFloat16))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
548 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderSignedZeroInfNanPreserveFloat32))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
552 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderSignedZeroInfNanPreserveFloat64))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
556 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderDenormPreserveFloat16))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
560 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderDenormPreserveFloat32))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
564 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderDenormPreserveFloat64))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
568 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderDenormFlushToZeroFloat16))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
572 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderDenormFlushToZeroFloat32))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
576 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderDenormFlushToZeroFloat64))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
580 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderRoundingModeRTEFloat16))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
584 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderRoundingModeRTEFloat32))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
588 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderRoundingModeRTEFloat64))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
592 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderRoundingModeRTZFloat16))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
596 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderRoundingModeRTZFloat32))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
600 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderRoundingModeRTZFloat64))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
604 :: Ptr Word32)) (Word32
maxUpdateAfterBindDescriptorsInAllPools)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
608 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderUniformBufferArrayNonUniformIndexingNative))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
612 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderSampledImageArrayNonUniformIndexingNative))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
616 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderStorageBufferArrayNonUniformIndexingNative))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
620 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderStorageImageArrayNonUniformIndexingNative))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
624 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderInputAttachmentArrayNonUniformIndexingNative))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
628 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
robustBufferAccessUpdateAfterBind))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
632 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
quadDivergentImplicitLod))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
636 :: Ptr Word32)) (Word32
maxPerStageDescriptorUpdateAfterBindSamplers)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
640 :: Ptr Word32)) (Word32
maxPerStageDescriptorUpdateAfterBindUniformBuffers)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
644 :: Ptr Word32)) (Word32
maxPerStageDescriptorUpdateAfterBindStorageBuffers)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
648 :: Ptr Word32)) (Word32
maxPerStageDescriptorUpdateAfterBindSampledImages)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
652 :: Ptr Word32)) (Word32
maxPerStageDescriptorUpdateAfterBindStorageImages)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
656 :: Ptr Word32)) (Word32
maxPerStageDescriptorUpdateAfterBindInputAttachments)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
660 :: Ptr Word32)) (Word32
maxPerStageUpdateAfterBindResources)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
664 :: Ptr Word32)) (Word32
maxDescriptorSetUpdateAfterBindSamplers)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
668 :: Ptr Word32)) (Word32
maxDescriptorSetUpdateAfterBindUniformBuffers)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
672 :: Ptr Word32)) (Word32
maxDescriptorSetUpdateAfterBindUniformBuffersDynamic)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
676 :: Ptr Word32)) (Word32
maxDescriptorSetUpdateAfterBindStorageBuffers)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
680 :: Ptr Word32)) (Word32
maxDescriptorSetUpdateAfterBindStorageBuffersDynamic)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
684 :: Ptr Word32)) (Word32
maxDescriptorSetUpdateAfterBindSampledImages)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
688 :: Ptr Word32)) (Word32
maxDescriptorSetUpdateAfterBindStorageImages)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
692 :: Ptr Word32)) (Word32
maxDescriptorSetUpdateAfterBindInputAttachments)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
696 :: Ptr ResolveModeFlags)) (ResolveModeFlags
supportedDepthResolveModes)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
700 :: Ptr ResolveModeFlags)) (ResolveModeFlags
supportedStencilResolveModes)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
704 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
independentResolveNone))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
708 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
independentResolve))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
712 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
filterMinmaxSingleComponentFormats))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
716 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
filterMinmaxImageComponentMapping))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
720 :: Ptr Word64)) (DeviceSize
maxTimelineSemaphoreValueDifference)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
728 :: Ptr SampleCountFlags)) (SampleCountFlags
framebufferIntegerColorSampleCounts)
IO b
f
cStructSize :: Int
cStructSize = Int
736
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b. Ptr PhysicalDeviceVulkan12Properties -> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceVulkan12Properties
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_VULKAN_1_2_PROPERTIES)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
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 PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DriverId)) (forall a. Zero a => a
zero)
forall (n :: Nat).
KnownNat n =>
Ptr (FixedArray n CChar) -> ByteString -> IO ()
pokeFixedLengthNullTerminatedByteString ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr (FixedArray MAX_DRIVER_NAME_SIZE CChar))) (forall a. Monoid a => a
mempty)
forall (n :: Nat).
KnownNat n =>
Ptr (FixedArray n CChar) -> ByteString -> IO ()
pokeFixedLengthNullTerminatedByteString ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
276 :: Ptr (FixedArray MAX_DRIVER_INFO_SIZE CChar))) (forall a. Monoid a => a
mempty)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
532 :: Ptr ConformanceVersion)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
536 :: Ptr ShaderFloatControlsIndependence)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
540 :: Ptr ShaderFloatControlsIndependence)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
544 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
548 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
552 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
556 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
560 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
564 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
568 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
572 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
576 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
580 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
584 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
588 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
592 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
596 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
600 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
604 :: Ptr Word32)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
608 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
612 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
616 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
620 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
624 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
628 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
632 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
636 :: Ptr Word32)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
640 :: Ptr Word32)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
644 :: Ptr Word32)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
648 :: Ptr Word32)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
652 :: Ptr Word32)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
656 :: Ptr Word32)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
660 :: Ptr Word32)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
664 :: Ptr Word32)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
668 :: Ptr Word32)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
672 :: Ptr Word32)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
676 :: Ptr Word32)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
680 :: Ptr Word32)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
684 :: Ptr Word32)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
688 :: Ptr Word32)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
692 :: Ptr Word32)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
696 :: Ptr ResolveModeFlags)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
700 :: Ptr ResolveModeFlags)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
704 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
708 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
712 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
716 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
720 :: Ptr Word64)) (forall a. Zero a => a
zero)
IO b
f
instance FromCStruct PhysicalDeviceVulkan12Properties where
peekCStruct :: Ptr PhysicalDeviceVulkan12Properties
-> IO PhysicalDeviceVulkan12Properties
peekCStruct Ptr PhysicalDeviceVulkan12Properties
p = do
DriverId
driverID <- forall a. Storable a => Ptr a -> IO a
peek @DriverId ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DriverId))
ByteString
driverName <- CString -> IO ByteString
packCString (forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr (FixedArray MAX_DRIVER_NAME_SIZE CChar))))
ByteString
driverInfo <- CString -> IO ByteString
packCString (forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
276 :: Ptr (FixedArray MAX_DRIVER_INFO_SIZE CChar))))
ConformanceVersion
conformanceVersion <- forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @ConformanceVersion ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
532 :: Ptr ConformanceVersion))
ShaderFloatControlsIndependence
denormBehaviorIndependence <- forall a. Storable a => Ptr a -> IO a
peek @ShaderFloatControlsIndependence ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
536 :: Ptr ShaderFloatControlsIndependence))
ShaderFloatControlsIndependence
roundingModeIndependence <- forall a. Storable a => Ptr a -> IO a
peek @ShaderFloatControlsIndependence ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
540 :: Ptr ShaderFloatControlsIndependence))
Bool32
shaderSignedZeroInfNanPreserveFloat16 <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
544 :: Ptr Bool32))
Bool32
shaderSignedZeroInfNanPreserveFloat32 <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
548 :: Ptr Bool32))
Bool32
shaderSignedZeroInfNanPreserveFloat64 <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
552 :: Ptr Bool32))
Bool32
shaderDenormPreserveFloat16 <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
556 :: Ptr Bool32))
Bool32
shaderDenormPreserveFloat32 <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
560 :: Ptr Bool32))
Bool32
shaderDenormPreserveFloat64 <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
564 :: Ptr Bool32))
Bool32
shaderDenormFlushToZeroFloat16 <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
568 :: Ptr Bool32))
Bool32
shaderDenormFlushToZeroFloat32 <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
572 :: Ptr Bool32))
Bool32
shaderDenormFlushToZeroFloat64 <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
576 :: Ptr Bool32))
Bool32
shaderRoundingModeRTEFloat16 <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
580 :: Ptr Bool32))
Bool32
shaderRoundingModeRTEFloat32 <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
584 :: Ptr Bool32))
Bool32
shaderRoundingModeRTEFloat64 <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
588 :: Ptr Bool32))
Bool32
shaderRoundingModeRTZFloat16 <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
592 :: Ptr Bool32))
Bool32
shaderRoundingModeRTZFloat32 <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
596 :: Ptr Bool32))
Bool32
shaderRoundingModeRTZFloat64 <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
600 :: Ptr Bool32))
Word32
maxUpdateAfterBindDescriptorsInAllPools <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
604 :: Ptr Word32))
Bool32
shaderUniformBufferArrayNonUniformIndexingNative <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
608 :: Ptr Bool32))
Bool32
shaderSampledImageArrayNonUniformIndexingNative <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
612 :: Ptr Bool32))
Bool32
shaderStorageBufferArrayNonUniformIndexingNative <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
616 :: Ptr Bool32))
Bool32
shaderStorageImageArrayNonUniformIndexingNative <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
620 :: Ptr Bool32))
Bool32
shaderInputAttachmentArrayNonUniformIndexingNative <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
624 :: Ptr Bool32))
Bool32
robustBufferAccessUpdateAfterBind <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
628 :: Ptr Bool32))
Bool32
quadDivergentImplicitLod <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
632 :: Ptr Bool32))
Word32
maxPerStageDescriptorUpdateAfterBindSamplers <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
636 :: Ptr Word32))
Word32
maxPerStageDescriptorUpdateAfterBindUniformBuffers <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
640 :: Ptr Word32))
Word32
maxPerStageDescriptorUpdateAfterBindStorageBuffers <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
644 :: Ptr Word32))
Word32
maxPerStageDescriptorUpdateAfterBindSampledImages <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
648 :: Ptr Word32))
Word32
maxPerStageDescriptorUpdateAfterBindStorageImages <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
652 :: Ptr Word32))
Word32
maxPerStageDescriptorUpdateAfterBindInputAttachments <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
656 :: Ptr Word32))
Word32
maxPerStageUpdateAfterBindResources <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
660 :: Ptr Word32))
Word32
maxDescriptorSetUpdateAfterBindSamplers <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
664 :: Ptr Word32))
Word32
maxDescriptorSetUpdateAfterBindUniformBuffers <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
668 :: Ptr Word32))
Word32
maxDescriptorSetUpdateAfterBindUniformBuffersDynamic <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
672 :: Ptr Word32))
Word32
maxDescriptorSetUpdateAfterBindStorageBuffers <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
676 :: Ptr Word32))
Word32
maxDescriptorSetUpdateAfterBindStorageBuffersDynamic <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
680 :: Ptr Word32))
Word32
maxDescriptorSetUpdateAfterBindSampledImages <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
684 :: Ptr Word32))
Word32
maxDescriptorSetUpdateAfterBindStorageImages <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
688 :: Ptr Word32))
Word32
maxDescriptorSetUpdateAfterBindInputAttachments <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
692 :: Ptr Word32))
ResolveModeFlags
supportedDepthResolveModes <- forall a. Storable a => Ptr a -> IO a
peek @ResolveModeFlags ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
696 :: Ptr ResolveModeFlags))
ResolveModeFlags
supportedStencilResolveModes <- forall a. Storable a => Ptr a -> IO a
peek @ResolveModeFlags ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
700 :: Ptr ResolveModeFlags))
Bool32
independentResolveNone <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
704 :: Ptr Bool32))
Bool32
independentResolve <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
708 :: Ptr Bool32))
Bool32
filterMinmaxSingleComponentFormats <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
712 :: Ptr Bool32))
Bool32
filterMinmaxImageComponentMapping <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
716 :: Ptr Bool32))
DeviceSize
maxTimelineSemaphoreValueDifference <- forall a. Storable a => Ptr a -> IO a
peek @Word64 ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
720 :: Ptr Word64))
SampleCountFlags
framebufferIntegerColorSampleCounts <- forall a. Storable a => Ptr a -> IO a
peek @SampleCountFlags ((Ptr PhysicalDeviceVulkan12Properties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
728 :: Ptr SampleCountFlags))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ DriverId
-> ByteString
-> ByteString
-> ConformanceVersion
-> ShaderFloatControlsIndependence
-> ShaderFloatControlsIndependence
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Word32
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> ResolveModeFlags
-> ResolveModeFlags
-> Bool
-> Bool
-> Bool
-> Bool
-> DeviceSize
-> SampleCountFlags
-> PhysicalDeviceVulkan12Properties
PhysicalDeviceVulkan12Properties
DriverId
driverID
ByteString
driverName
ByteString
driverInfo
ConformanceVersion
conformanceVersion
ShaderFloatControlsIndependence
denormBehaviorIndependence
ShaderFloatControlsIndependence
roundingModeIndependence
(Bool32 -> Bool
bool32ToBool Bool32
shaderSignedZeroInfNanPreserveFloat16)
(Bool32 -> Bool
bool32ToBool Bool32
shaderSignedZeroInfNanPreserveFloat32)
(Bool32 -> Bool
bool32ToBool Bool32
shaderSignedZeroInfNanPreserveFloat64)
(Bool32 -> Bool
bool32ToBool Bool32
shaderDenormPreserveFloat16)
(Bool32 -> Bool
bool32ToBool Bool32
shaderDenormPreserveFloat32)
(Bool32 -> Bool
bool32ToBool Bool32
shaderDenormPreserveFloat64)
(Bool32 -> Bool
bool32ToBool Bool32
shaderDenormFlushToZeroFloat16)
(Bool32 -> Bool
bool32ToBool Bool32
shaderDenormFlushToZeroFloat32)
(Bool32 -> Bool
bool32ToBool Bool32
shaderDenormFlushToZeroFloat64)
(Bool32 -> Bool
bool32ToBool Bool32
shaderRoundingModeRTEFloat16)
(Bool32 -> Bool
bool32ToBool Bool32
shaderRoundingModeRTEFloat32)
(Bool32 -> Bool
bool32ToBool Bool32
shaderRoundingModeRTEFloat64)
(Bool32 -> Bool
bool32ToBool Bool32
shaderRoundingModeRTZFloat16)
(Bool32 -> Bool
bool32ToBool Bool32
shaderRoundingModeRTZFloat32)
(Bool32 -> Bool
bool32ToBool Bool32
shaderRoundingModeRTZFloat64)
Word32
maxUpdateAfterBindDescriptorsInAllPools
(Bool32 -> Bool
bool32ToBool Bool32
shaderUniformBufferArrayNonUniformIndexingNative)
(Bool32 -> Bool
bool32ToBool Bool32
shaderSampledImageArrayNonUniformIndexingNative)
(Bool32 -> Bool
bool32ToBool Bool32
shaderStorageBufferArrayNonUniformIndexingNative)
(Bool32 -> Bool
bool32ToBool Bool32
shaderStorageImageArrayNonUniformIndexingNative)
(Bool32 -> Bool
bool32ToBool Bool32
shaderInputAttachmentArrayNonUniformIndexingNative)
(Bool32 -> Bool
bool32ToBool Bool32
robustBufferAccessUpdateAfterBind)
(Bool32 -> Bool
bool32ToBool Bool32
quadDivergentImplicitLod)
Word32
maxPerStageDescriptorUpdateAfterBindSamplers
Word32
maxPerStageDescriptorUpdateAfterBindUniformBuffers
Word32
maxPerStageDescriptorUpdateAfterBindStorageBuffers
Word32
maxPerStageDescriptorUpdateAfterBindSampledImages
Word32
maxPerStageDescriptorUpdateAfterBindStorageImages
Word32
maxPerStageDescriptorUpdateAfterBindInputAttachments
Word32
maxPerStageUpdateAfterBindResources
Word32
maxDescriptorSetUpdateAfterBindSamplers
Word32
maxDescriptorSetUpdateAfterBindUniformBuffers
Word32
maxDescriptorSetUpdateAfterBindUniformBuffersDynamic
Word32
maxDescriptorSetUpdateAfterBindStorageBuffers
Word32
maxDescriptorSetUpdateAfterBindStorageBuffersDynamic
Word32
maxDescriptorSetUpdateAfterBindSampledImages
Word32
maxDescriptorSetUpdateAfterBindStorageImages
Word32
maxDescriptorSetUpdateAfterBindInputAttachments
ResolveModeFlags
supportedDepthResolveModes
ResolveModeFlags
supportedStencilResolveModes
(Bool32 -> Bool
bool32ToBool Bool32
independentResolveNone)
(Bool32 -> Bool
bool32ToBool Bool32
independentResolve)
(Bool32 -> Bool
bool32ToBool Bool32
filterMinmaxSingleComponentFormats)
(Bool32 -> Bool
bool32ToBool Bool32
filterMinmaxImageComponentMapping)
DeviceSize
maxTimelineSemaphoreValueDifference
SampleCountFlags
framebufferIntegerColorSampleCounts
instance Storable PhysicalDeviceVulkan12Properties where
sizeOf :: PhysicalDeviceVulkan12Properties -> Int
sizeOf ~PhysicalDeviceVulkan12Properties
_ = Int
736
alignment :: PhysicalDeviceVulkan12Properties -> Int
alignment ~PhysicalDeviceVulkan12Properties
_ = Int
8
peek :: Ptr PhysicalDeviceVulkan12Properties
-> IO PhysicalDeviceVulkan12Properties
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr PhysicalDeviceVulkan12Properties
-> PhysicalDeviceVulkan12Properties -> IO ()
poke Ptr PhysicalDeviceVulkan12Properties
ptr PhysicalDeviceVulkan12Properties
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceVulkan12Properties
ptr PhysicalDeviceVulkan12Properties
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PhysicalDeviceVulkan12Properties where
zero :: PhysicalDeviceVulkan12Properties
zero = DriverId
-> ByteString
-> ByteString
-> ConformanceVersion
-> ShaderFloatControlsIndependence
-> ShaderFloatControlsIndependence
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Word32
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> Word32
-> ResolveModeFlags
-> ResolveModeFlags
-> Bool
-> Bool
-> Bool
-> Bool
-> DeviceSize
-> SampleCountFlags
-> PhysicalDeviceVulkan12Properties
PhysicalDeviceVulkan12Properties
forall a. Zero a => a
zero
forall a. Monoid a => a
mempty
forall a. Monoid a => a
mempty
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
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero