{-# 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 (allocaBytesAligned)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import Data.ByteString (packCString)
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Cont (evalContT)
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 Control.Monad.Trans.Cont (ContT(..))
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.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
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.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Core10.APIConstants (UUID_SIZE)
import Vulkan.Zero (Zero(..))
import Vulkan.Version (pattern MAKE_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 -> (Void# -> r) -> (Void# -> r) -> r
API_VERSION_1_2 = MAKE_VERSION 1 2 0


-- | VkPhysicalDeviceVulkan11Features - Structure describing the Vulkan 1.1
-- features that can be supported by an implementation
--
-- = Members
--
-- The members of the 'PhysicalDeviceVulkan11Features' structure describe
-- the following features:
--
-- = Description
--
-- If the 'PhysicalDeviceVulkan11Features' structure is included in the
-- @pNext@ chain of
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceFeatures2',
-- it is filled with values indicating whether each feature is supported.
-- 'PhysicalDeviceVulkan11Features' /can/ also be used in the @pNext@ chain
-- of 'Vulkan.Core10.Device.DeviceCreateInfo' to enable the features.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDeviceVulkan11Features = PhysicalDeviceVulkan11Features
  { -- | @storageBuffer16BitAccess@ specifies whether objects in the
    -- @StorageBuffer@ or @PhysicalStorageBuffer@ storage class with the
    -- @Block@ decoration /can/ have 16-bit integer and 16-bit floating-point
    -- members. If this feature is not enabled, 16-bit integer or 16-bit
    -- floating-point members /must/ not be used in such objects. This also
    -- specifies whether shader modules /can/ declare the
    -- @StorageBuffer16BitAccess@ capability.
    PhysicalDeviceVulkan11Features -> Bool
storageBuffer16BitAccess :: Bool
  , -- | @uniformAndStorageBuffer16BitAccess@ specifies whether objects in the
    -- @Uniform@ storage class with the @Block@ decoration and in the
    -- @StorageBuffer@ or @PhysicalStorageBuffer@ storage class with the same
    -- decoration /can/ have 16-bit integer and 16-bit floating-point members.
    -- If this feature is not enabled, 16-bit integer or 16-bit floating-point
    -- members /must/ not be used in such objects. This also specifies whether
    -- shader modules /can/ declare the @UniformAndStorageBuffer16BitAccess@
    -- capability.
    PhysicalDeviceVulkan11Features -> Bool
uniformAndStorageBuffer16BitAccess :: Bool
  , -- | @storagePushConstant16@ specifies whether objects in the @PushConstant@
    -- storage class /can/ have 16-bit integer and 16-bit floating-point
    -- members. If this feature is not enabled, 16-bit integer or
    -- floating-point members /must/ not be used in such objects. This also
    -- specifies whether shader modules /can/ declare the
    -- @StoragePushConstant16@ capability.
    PhysicalDeviceVulkan11Features -> Bool
storagePushConstant16 :: Bool
  , -- | @storageInputOutput16@ specifies whether objects in the @Input@ and
    -- @Output@ storage classes /can/ have 16-bit integer and 16-bit
    -- floating-point members. If this feature is not enabled, 16-bit integer
    -- or 16-bit floating-point members /must/ not be used in such objects.
    -- This also specifies whether shader modules /can/ declare the
    -- @StorageInputOutput16@ capability.
    PhysicalDeviceVulkan11Features -> Bool
storageInputOutput16 :: Bool
  , -- | @multiview@ specifies whether the implementation supports multiview
    -- rendering within a render pass. If this feature is not enabled, the view
    -- mask of each subpass /must/ always be zero.
    PhysicalDeviceVulkan11Features -> Bool
multiview :: Bool
  , -- | @multiviewGeometryShader@ specifies whether the implementation supports
    -- multiview rendering within a render pass, with
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#geometry geometry shaders>.
    -- If this feature is not enabled, then a pipeline compiled against a
    -- subpass with a non-zero view mask /must/ not include a geometry shader.
    PhysicalDeviceVulkan11Features -> Bool
multiviewGeometryShader :: Bool
  , -- | @multiviewTessellationShader@ specifies whether the implementation
    -- supports multiview rendering within a render pass, with
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#tessellation tessellation shaders>.
    -- If this feature is not enabled, then a pipeline compiled against a
    -- subpass with a non-zero view mask /must/ not include any tessellation
    -- shaders.
    PhysicalDeviceVulkan11Features -> Bool
multiviewTessellationShader :: Bool
  , -- | @variablePointersStorageBuffer@ specifies whether the implementation
    -- supports the SPIR-V @VariablePointersStorageBuffer@ capability. When
    -- this feature is not enabled, shader modules /must/ not declare the
    -- @SPV_KHR_variable_pointers@ extension or the
    -- @VariablePointersStorageBuffer@ capability.
    PhysicalDeviceVulkan11Features -> Bool
variablePointersStorageBuffer :: Bool
  , -- | @variablePointers@ specifies whether the implementation supports the
    -- SPIR-V @VariablePointers@ capability. When this feature is not enabled,
    -- shader modules /must/ not declare the @VariablePointers@ capability.
    PhysicalDeviceVulkan11Features -> Bool
variablePointers :: Bool
  , -- | @protectedMemory@ specifies whether protected memory is supported.
    PhysicalDeviceVulkan11Features -> Bool
protectedMemory :: Bool
  , -- | @samplerYcbcrConversion@ specifies whether the implementation supports
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#samplers-YCbCr-conversion sampler Y′CBCR conversion>.
    -- If @samplerYcbcrConversion@ is 'Vulkan.Core10.FundamentalTypes.FALSE',
    -- sampler Y′CBCR conversion is not supported, and samplers using sampler
    -- Y′CBCR conversion /must/ not be used.
    PhysicalDeviceVulkan11Features -> Bool
samplerYcbcrConversion :: Bool
  , -- | @shaderDrawParameters@ specifies whether shader draw parameters are
    -- supported.
    PhysicalDeviceVulkan11Features -> Bool
shaderDrawParameters :: Bool
  }
  deriving (Typeable, PhysicalDeviceVulkan11Features
-> PhysicalDeviceVulkan11Features -> Bool
(PhysicalDeviceVulkan11Features
 -> PhysicalDeviceVulkan11Features -> Bool)
-> (PhysicalDeviceVulkan11Features
    -> PhysicalDeviceVulkan11Features -> Bool)
-> Eq PhysicalDeviceVulkan11Features
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 :: PhysicalDeviceVulkan11Features
-> (Ptr PhysicalDeviceVulkan11Features -> IO b) -> IO b
withCStruct x :: PhysicalDeviceVulkan11Features
x f :: Ptr PhysicalDeviceVulkan11Features -> IO b
f = Int -> Int -> (Ptr PhysicalDeviceVulkan11Features -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 64 8 ((Ptr PhysicalDeviceVulkan11Features -> IO b) -> IO b)
-> (Ptr PhysicalDeviceVulkan11Features -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr PhysicalDeviceVulkan11Features
p -> Ptr PhysicalDeviceVulkan11Features
-> PhysicalDeviceVulkan11Features -> IO b -> IO b
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 :: Ptr PhysicalDeviceVulkan11Features
-> PhysicalDeviceVulkan11Features -> IO b -> IO b
pokeCStruct p :: Ptr PhysicalDeviceVulkan11Features
p PhysicalDeviceVulkan11Features{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Features
p Ptr PhysicalDeviceVulkan11Features -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_VULKAN_1_1_FEATURES)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Features
p Ptr PhysicalDeviceVulkan11Features -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Features
p Ptr PhysicalDeviceVulkan11Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
storageBuffer16BitAccess))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Features
p Ptr PhysicalDeviceVulkan11Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
uniformAndStorageBuffer16BitAccess))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Features
p Ptr PhysicalDeviceVulkan11Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
storagePushConstant16))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Features
p Ptr PhysicalDeviceVulkan11Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
storageInputOutput16))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Features
p Ptr PhysicalDeviceVulkan11Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
multiview))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Features
p Ptr PhysicalDeviceVulkan11Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 36 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
multiviewGeometryShader))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Features
p Ptr PhysicalDeviceVulkan11Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
multiviewTessellationShader))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Features
p Ptr PhysicalDeviceVulkan11Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 44 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
variablePointersStorageBuffer))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Features
p Ptr PhysicalDeviceVulkan11Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
variablePointers))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Features
p Ptr PhysicalDeviceVulkan11Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 52 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
protectedMemory))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Features
p Ptr PhysicalDeviceVulkan11Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
samplerYcbcrConversion))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Features
p Ptr PhysicalDeviceVulkan11Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 60 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderDrawParameters))
    IO b
f
  cStructSize :: Int
cStructSize = 64
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr PhysicalDeviceVulkan11Features -> IO b -> IO b
pokeZeroCStruct p :: Ptr PhysicalDeviceVulkan11Features
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Features
p Ptr PhysicalDeviceVulkan11Features -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_VULKAN_1_1_FEATURES)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Features
p Ptr PhysicalDeviceVulkan11Features -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Features
p Ptr PhysicalDeviceVulkan11Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Features
p Ptr PhysicalDeviceVulkan11Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Features
p Ptr PhysicalDeviceVulkan11Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Features
p Ptr PhysicalDeviceVulkan11Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Features
p Ptr PhysicalDeviceVulkan11Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Features
p Ptr PhysicalDeviceVulkan11Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 36 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Features
p Ptr PhysicalDeviceVulkan11Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Features
p Ptr PhysicalDeviceVulkan11Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 44 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Features
p Ptr PhysicalDeviceVulkan11Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Features
p Ptr PhysicalDeviceVulkan11Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 52 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Features
p Ptr PhysicalDeviceVulkan11Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Features
p Ptr PhysicalDeviceVulkan11Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 60 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    IO b
f

instance FromCStruct PhysicalDeviceVulkan11Features where
  peekCStruct :: Ptr PhysicalDeviceVulkan11Features
-> IO PhysicalDeviceVulkan11Features
peekCStruct p :: Ptr PhysicalDeviceVulkan11Features
p = do
    Bool32
storageBuffer16BitAccess <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan11Features
p Ptr PhysicalDeviceVulkan11Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32))
    Bool32
uniformAndStorageBuffer16BitAccess <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan11Features
p Ptr PhysicalDeviceVulkan11Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Bool32))
    Bool32
storagePushConstant16 <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan11Features
p Ptr PhysicalDeviceVulkan11Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Bool32))
    Bool32
storageInputOutput16 <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan11Features
p Ptr PhysicalDeviceVulkan11Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr Bool32))
    Bool32
multiview <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan11Features
p Ptr PhysicalDeviceVulkan11Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Bool32))
    Bool32
multiviewGeometryShader <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan11Features
p Ptr PhysicalDeviceVulkan11Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 36 :: Ptr Bool32))
    Bool32
multiviewTessellationShader <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan11Features
p Ptr PhysicalDeviceVulkan11Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr Bool32))
    Bool32
variablePointersStorageBuffer <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan11Features
p Ptr PhysicalDeviceVulkan11Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 44 :: Ptr Bool32))
    Bool32
variablePointers <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan11Features
p Ptr PhysicalDeviceVulkan11Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr Bool32))
    Bool32
protectedMemory <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan11Features
p Ptr PhysicalDeviceVulkan11Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 52 :: Ptr Bool32))
    Bool32
samplerYcbcrConversion <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan11Features
p Ptr PhysicalDeviceVulkan11Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr Bool32))
    Bool32
shaderDrawParameters <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan11Features
p Ptr PhysicalDeviceVulkan11Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 60 :: Ptr Bool32))
    PhysicalDeviceVulkan11Features -> IO PhysicalDeviceVulkan11Features
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDeviceVulkan11Features
 -> IO PhysicalDeviceVulkan11Features)
-> PhysicalDeviceVulkan11Features
-> IO PhysicalDeviceVulkan11Features
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
_ = 64
  alignment :: PhysicalDeviceVulkan11Features -> Int
alignment ~PhysicalDeviceVulkan11Features
_ = 8
  peek :: Ptr PhysicalDeviceVulkan11Features
-> IO PhysicalDeviceVulkan11Features
peek = Ptr PhysicalDeviceVulkan11Features
-> IO PhysicalDeviceVulkan11Features
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: Ptr PhysicalDeviceVulkan11Features
-> PhysicalDeviceVulkan11Features -> IO ()
poke ptr :: Ptr PhysicalDeviceVulkan11Features
ptr poked :: PhysicalDeviceVulkan11Features
poked = Ptr PhysicalDeviceVulkan11Features
-> PhysicalDeviceVulkan11Features -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceVulkan11Features
ptr PhysicalDeviceVulkan11Features
poked (() -> IO ()
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
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero


-- | VkPhysicalDeviceVulkan11Properties - Structure specifying physical
-- device properties for functionality promoted to Vulkan 1.1
--
-- = Description
--
-- The members of 'PhysicalDeviceVulkan11Properties' /must/ have the same
-- values as the corresponding members of
-- 'Vulkan.Core11.Promoted_From_VK_KHR_external_memory_capabilities.PhysicalDeviceIDProperties',
-- 'Vulkan.Core11.Originally_Based_On_VK_KHR_subgroup.PhysicalDeviceSubgroupProperties',
-- 'Vulkan.Core11.Promoted_From_VK_KHR_maintenance2.PhysicalDevicePointClippingProperties',
-- 'Vulkan.Core11.Promoted_From_VK_KHR_multiview.PhysicalDeviceMultiviewProperties',
-- 'Vulkan.Core11.Originally_Based_On_VK_KHR_protected_memory.PhysicalDeviceProtectedMemoryProperties',
-- and
-- 'Vulkan.Core11.Promoted_From_VK_KHR_maintenance3.PhysicalDeviceMaintenance3Properties'.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.FundamentalTypes.DeviceSize',
-- 'Vulkan.Core11.Enums.PointClippingBehavior.PointClippingBehavior',
-- 'Vulkan.Core10.Enums.ShaderStageFlagBits.ShaderStageFlags',
-- 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'Vulkan.Core11.Enums.SubgroupFeatureFlagBits.SubgroupFeatureFlags'
data PhysicalDeviceVulkan11Properties = PhysicalDeviceVulkan11Properties
  { -- | @deviceUUID@ is an array of 'Vulkan.Core10.APIConstants.UUID_SIZE'
    -- @uint8_t@ values representing a universally unique identifier for the
    -- device.
    PhysicalDeviceVulkan11Properties -> ByteString
deviceUUID :: ByteString
  , -- | @driverUUID@ is an array of 'Vulkan.Core10.APIConstants.UUID_SIZE'
    -- @uint8_t@ values representing a universally unique identifier for the
    -- driver build in use by the device.
    PhysicalDeviceVulkan11Properties -> ByteString
driverUUID :: ByteString
  , -- | @deviceLUID@ is an array of 'Vulkan.Core10.APIConstants.LUID_SIZE'
    -- @uint8_t@ values representing a locally unique identifier for the
    -- device.
    PhysicalDeviceVulkan11Properties -> ByteString
deviceLUID :: ByteString
  , -- | @deviceNodeMask@ is a @uint32_t@ bitfield identifying the node within a
    -- linked device adapter corresponding to the device.
    PhysicalDeviceVulkan11Properties -> Word32
deviceNodeMask :: Word32
  , -- | @deviceLUIDValid@ is a boolean value that will be
    -- 'Vulkan.Core10.FundamentalTypes.TRUE' if @deviceLUID@ contains a valid
    -- LUID and @deviceNodeMask@ contains a valid node mask, and
    -- 'Vulkan.Core10.FundamentalTypes.FALSE' if they do not.
    PhysicalDeviceVulkan11Properties -> Bool
deviceLUIDValid :: Bool
  , -- | @subgroupSize@ is the default number of invocations in each subgroup.
    -- @subgroupSize@ is at least 1 if any of the physical device’s queues
    -- support 'Vulkan.Core10.Enums.QueueFlagBits.QUEUE_GRAPHICS_BIT' or
    -- 'Vulkan.Core10.Enums.QueueFlagBits.QUEUE_COMPUTE_BIT'. @subgroupSize@ is
    -- a power-of-two.
    PhysicalDeviceVulkan11Properties -> Word32
subgroupSize :: Word32
  , -- | @subgroupSupportedStages@ is a bitfield of
    -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.ShaderStageFlagBits' describing
    -- the shader stages that subgroup operations are supported in.
    -- @subgroupSupportedStages@ will have the
    -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_COMPUTE_BIT' bit
    -- set if any of the physical device’s queues support
    -- 'Vulkan.Core10.Enums.QueueFlagBits.QUEUE_COMPUTE_BIT'.
    PhysicalDeviceVulkan11Properties -> ShaderStageFlags
subgroupSupportedStages :: ShaderStageFlags
  , -- | @subgroupSupportedOperations@ is a bitmask of
    -- 'Vulkan.Core11.Enums.SubgroupFeatureFlagBits.SubgroupFeatureFlagBits'
    -- specifying the sets of subgroup operations supported on this device.
    -- @subgroupSupportedOperations@ will have the
    -- 'Vulkan.Core11.Enums.SubgroupFeatureFlagBits.SUBGROUP_FEATURE_BASIC_BIT'
    -- bit set if any of the physical device’s queues support
    -- 'Vulkan.Core10.Enums.QueueFlagBits.QUEUE_GRAPHICS_BIT' or
    -- 'Vulkan.Core10.Enums.QueueFlagBits.QUEUE_COMPUTE_BIT'.
    PhysicalDeviceVulkan11Properties -> SubgroupFeatureFlags
subgroupSupportedOperations :: SubgroupFeatureFlags
  , -- | @subgroupQuadOperationsInAllStages@ is a boolean specifying whether
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-subgroup-quad quad subgroup operations>
    -- are available in all stages, or are restricted to fragment and compute
    -- stages.
    PhysicalDeviceVulkan11Properties -> Bool
subgroupQuadOperationsInAllStages :: Bool
  , -- | @pointClippingBehavior@ is a
    -- 'Vulkan.Core11.Enums.PointClippingBehavior.PointClippingBehavior' value
    -- specifying the point clipping behavior supported by the implementation.
    PhysicalDeviceVulkan11Properties -> PointClippingBehavior
pointClippingBehavior :: PointClippingBehavior
  , -- | @maxMultiviewViewCount@ is one greater than the maximum view index that
    -- /can/ be used in a subpass.
    PhysicalDeviceVulkan11Properties -> Word32
maxMultiviewViewCount :: Word32
  , -- | @maxMultiviewInstanceIndex@ is the maximum valid value of instance index
    -- allowed to be generated by a drawing command recorded within a subpass
    -- of a multiview render pass instance.
    PhysicalDeviceVulkan11Properties -> Word32
maxMultiviewInstanceIndex :: Word32
  , -- | @protectedNoFault@ specifies the behavior of the implementation when
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#memory-protected-access-rules protected memory access rules>
    -- are broken. If @protectedNoFault@ is
    -- 'Vulkan.Core10.FundamentalTypes.TRUE', breaking those rules will not
    -- result in process termination or device loss.
    PhysicalDeviceVulkan11Properties -> Bool
protectedNoFault :: Bool
  , -- | @maxPerSetDescriptors@ is a maximum number of descriptors (summed over
    -- all descriptor types) in a single descriptor set that is guaranteed to
    -- satisfy any implementation-dependent constraints on the size of a
    -- descriptor set itself. Applications /can/ query whether a descriptor set
    -- that goes beyond this limit is supported using
    -- 'Vulkan.Core11.Promoted_From_VK_KHR_maintenance3.getDescriptorSetLayoutSupport'.
    PhysicalDeviceVulkan11Properties -> Word32
maxPerSetDescriptors :: Word32
  , -- | @maxMemoryAllocationSize@ is the maximum size of a memory allocation
    -- that /can/ be created, even if there is more space available in the
    -- heap.
    PhysicalDeviceVulkan11Properties -> DeviceSize
maxMemoryAllocationSize :: DeviceSize
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceVulkan11Properties)
#endif
deriving instance Show PhysicalDeviceVulkan11Properties

instance ToCStruct PhysicalDeviceVulkan11Properties where
  withCStruct :: PhysicalDeviceVulkan11Properties
-> (Ptr PhysicalDeviceVulkan11Properties -> IO b) -> IO b
withCStruct x :: PhysicalDeviceVulkan11Properties
x f :: Ptr PhysicalDeviceVulkan11Properties -> IO b
f = Int
-> Int -> (Ptr PhysicalDeviceVulkan11Properties -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 112 8 ((Ptr PhysicalDeviceVulkan11Properties -> IO b) -> IO b)
-> (Ptr PhysicalDeviceVulkan11Properties -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr PhysicalDeviceVulkan11Properties
p -> Ptr PhysicalDeviceVulkan11Properties
-> PhysicalDeviceVulkan11Properties -> IO b -> IO b
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 :: Ptr PhysicalDeviceVulkan11Properties
-> PhysicalDeviceVulkan11Properties -> IO b -> IO b
pokeCStruct p :: Ptr PhysicalDeviceVulkan11Properties
p PhysicalDeviceVulkan11Properties{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Properties
p Ptr PhysicalDeviceVulkan11Properties -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_VULKAN_1_1_PROPERTIES)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Properties
p Ptr PhysicalDeviceVulkan11Properties -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr (FixedArray UUID_SIZE Word8) -> ByteString -> IO ()
forall (n :: Nat).
KnownNat n =>
Ptr (FixedArray n Word8) -> ByteString -> IO ()
pokeFixedLengthByteString ((Ptr PhysicalDeviceVulkan11Properties
p Ptr PhysicalDeviceVulkan11Properties
-> Int -> Ptr (FixedArray UUID_SIZE Word8)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr (FixedArray UUID_SIZE Word8))) (ByteString
deviceUUID)
    Ptr (FixedArray UUID_SIZE Word8) -> ByteString -> IO ()
forall (n :: Nat).
KnownNat n =>
Ptr (FixedArray n Word8) -> ByteString -> IO ()
pokeFixedLengthByteString ((Ptr PhysicalDeviceVulkan11Properties
p Ptr PhysicalDeviceVulkan11Properties
-> Int -> Ptr (FixedArray UUID_SIZE Word8)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr (FixedArray UUID_SIZE Word8))) (ByteString
driverUUID)
    Ptr (FixedArray LUID_SIZE Word8) -> ByteString -> IO ()
forall (n :: Nat).
KnownNat n =>
Ptr (FixedArray n Word8) -> ByteString -> IO ()
pokeFixedLengthByteString ((Ptr PhysicalDeviceVulkan11Properties
p Ptr PhysicalDeviceVulkan11Properties
-> Int -> Ptr (FixedArray LUID_SIZE Word8)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr (FixedArray LUID_SIZE Word8))) (ByteString
deviceLUID)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Properties
p Ptr PhysicalDeviceVulkan11Properties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr Word32)) (Word32
deviceNodeMask)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Properties
p Ptr PhysicalDeviceVulkan11Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 60 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
deviceLUIDValid))
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Properties
p Ptr PhysicalDeviceVulkan11Properties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64 :: Ptr Word32)) (Word32
subgroupSize)
    Ptr ShaderStageFlags -> ShaderStageFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Properties
p Ptr PhysicalDeviceVulkan11Properties -> Int -> Ptr ShaderStageFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 68 :: Ptr ShaderStageFlags)) (ShaderStageFlags
subgroupSupportedStages)
    Ptr SubgroupFeatureFlags -> SubgroupFeatureFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Properties
p Ptr PhysicalDeviceVulkan11Properties
-> Int -> Ptr SubgroupFeatureFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 72 :: Ptr SubgroupFeatureFlags)) (SubgroupFeatureFlags
subgroupSupportedOperations)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Properties
p Ptr PhysicalDeviceVulkan11Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 76 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
subgroupQuadOperationsInAllStages))
    Ptr PointClippingBehavior -> PointClippingBehavior -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Properties
p Ptr PhysicalDeviceVulkan11Properties
-> Int -> Ptr PointClippingBehavior
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 80 :: Ptr PointClippingBehavior)) (PointClippingBehavior
pointClippingBehavior)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Properties
p Ptr PhysicalDeviceVulkan11Properties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 84 :: Ptr Word32)) (Word32
maxMultiviewViewCount)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Properties
p Ptr PhysicalDeviceVulkan11Properties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 88 :: Ptr Word32)) (Word32
maxMultiviewInstanceIndex)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Properties
p Ptr PhysicalDeviceVulkan11Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 92 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
protectedNoFault))
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Properties
p Ptr PhysicalDeviceVulkan11Properties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 96 :: Ptr Word32)) (Word32
maxPerSetDescriptors)
    Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Properties
p Ptr PhysicalDeviceVulkan11Properties -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 104 :: Ptr DeviceSize)) (DeviceSize
maxMemoryAllocationSize)
    IO b
f
  cStructSize :: Int
cStructSize = 112
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr PhysicalDeviceVulkan11Properties -> IO b -> IO b
pokeZeroCStruct p :: Ptr PhysicalDeviceVulkan11Properties
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Properties
p Ptr PhysicalDeviceVulkan11Properties -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_VULKAN_1_1_PROPERTIES)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Properties
p Ptr PhysicalDeviceVulkan11Properties -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr (FixedArray UUID_SIZE Word8) -> ByteString -> IO ()
forall (n :: Nat).
KnownNat n =>
Ptr (FixedArray n Word8) -> ByteString -> IO ()
pokeFixedLengthByteString ((Ptr PhysicalDeviceVulkan11Properties
p Ptr PhysicalDeviceVulkan11Properties
-> Int -> Ptr (FixedArray UUID_SIZE Word8)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr (FixedArray UUID_SIZE Word8))) (ByteString
forall a. Monoid a => a
mempty)
    Ptr (FixedArray UUID_SIZE Word8) -> ByteString -> IO ()
forall (n :: Nat).
KnownNat n =>
Ptr (FixedArray n Word8) -> ByteString -> IO ()
pokeFixedLengthByteString ((Ptr PhysicalDeviceVulkan11Properties
p Ptr PhysicalDeviceVulkan11Properties
-> Int -> Ptr (FixedArray UUID_SIZE Word8)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr (FixedArray UUID_SIZE Word8))) (ByteString
forall a. Monoid a => a
mempty)
    Ptr (FixedArray LUID_SIZE Word8) -> ByteString -> IO ()
forall (n :: Nat).
KnownNat n =>
Ptr (FixedArray n Word8) -> ByteString -> IO ()
pokeFixedLengthByteString ((Ptr PhysicalDeviceVulkan11Properties
p Ptr PhysicalDeviceVulkan11Properties
-> Int -> Ptr (FixedArray LUID_SIZE Word8)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr (FixedArray LUID_SIZE Word8))) (ByteString
forall a. Monoid a => a
mempty)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Properties
p Ptr PhysicalDeviceVulkan11Properties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Properties
p Ptr PhysicalDeviceVulkan11Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 60 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Properties
p Ptr PhysicalDeviceVulkan11Properties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr ShaderStageFlags -> ShaderStageFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Properties
p Ptr PhysicalDeviceVulkan11Properties -> Int -> Ptr ShaderStageFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 68 :: Ptr ShaderStageFlags)) (ShaderStageFlags
forall a. Zero a => a
zero)
    Ptr SubgroupFeatureFlags -> SubgroupFeatureFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Properties
p Ptr PhysicalDeviceVulkan11Properties
-> Int -> Ptr SubgroupFeatureFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 72 :: Ptr SubgroupFeatureFlags)) (SubgroupFeatureFlags
forall a. Zero a => a
zero)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Properties
p Ptr PhysicalDeviceVulkan11Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 76 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr PointClippingBehavior -> PointClippingBehavior -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Properties
p Ptr PhysicalDeviceVulkan11Properties
-> Int -> Ptr PointClippingBehavior
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 80 :: Ptr PointClippingBehavior)) (PointClippingBehavior
forall a. Zero a => a
zero)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Properties
p Ptr PhysicalDeviceVulkan11Properties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 84 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Properties
p Ptr PhysicalDeviceVulkan11Properties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 88 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Properties
p Ptr PhysicalDeviceVulkan11Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 92 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Properties
p Ptr PhysicalDeviceVulkan11Properties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 96 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan11Properties
p Ptr PhysicalDeviceVulkan11Properties -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 104 :: Ptr DeviceSize)) (DeviceSize
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct PhysicalDeviceVulkan11Properties where
  peekCStruct :: Ptr PhysicalDeviceVulkan11Properties
-> IO PhysicalDeviceVulkan11Properties
peekCStruct p :: Ptr PhysicalDeviceVulkan11Properties
p = do
    ByteString
deviceUUID <- Ptr (FixedArray UUID_SIZE Word8) -> IO ByteString
forall (n :: Nat).
KnownNat n =>
Ptr (FixedArray n Word8) -> IO ByteString
peekByteStringFromSizedVectorPtr ((Ptr PhysicalDeviceVulkan11Properties
p Ptr PhysicalDeviceVulkan11Properties
-> Int -> Ptr (FixedArray UUID_SIZE Word8)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr (FixedArray UUID_SIZE Word8)))
    ByteString
driverUUID <- Ptr (FixedArray UUID_SIZE Word8) -> IO ByteString
forall (n :: Nat).
KnownNat n =>
Ptr (FixedArray n Word8) -> IO ByteString
peekByteStringFromSizedVectorPtr ((Ptr PhysicalDeviceVulkan11Properties
p Ptr PhysicalDeviceVulkan11Properties
-> Int -> Ptr (FixedArray UUID_SIZE Word8)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr (FixedArray UUID_SIZE Word8)))
    ByteString
deviceLUID <- Ptr (FixedArray LUID_SIZE Word8) -> IO ByteString
forall (n :: Nat).
KnownNat n =>
Ptr (FixedArray n Word8) -> IO ByteString
peekByteStringFromSizedVectorPtr ((Ptr PhysicalDeviceVulkan11Properties
p Ptr PhysicalDeviceVulkan11Properties
-> Int -> Ptr (FixedArray LUID_SIZE Word8)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr (FixedArray LUID_SIZE Word8)))
    Word32
deviceNodeMask <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceVulkan11Properties
p Ptr PhysicalDeviceVulkan11Properties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr Word32))
    Bool32
deviceLUIDValid <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan11Properties
p Ptr PhysicalDeviceVulkan11Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 60 :: Ptr Bool32))
    Word32
subgroupSize <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceVulkan11Properties
p Ptr PhysicalDeviceVulkan11Properties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64 :: Ptr Word32))
    ShaderStageFlags
subgroupSupportedStages <- Ptr ShaderStageFlags -> IO ShaderStageFlags
forall a. Storable a => Ptr a -> IO a
peek @ShaderStageFlags ((Ptr PhysicalDeviceVulkan11Properties
p Ptr PhysicalDeviceVulkan11Properties -> Int -> Ptr ShaderStageFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 68 :: Ptr ShaderStageFlags))
    SubgroupFeatureFlags
subgroupSupportedOperations <- Ptr SubgroupFeatureFlags -> IO SubgroupFeatureFlags
forall a. Storable a => Ptr a -> IO a
peek @SubgroupFeatureFlags ((Ptr PhysicalDeviceVulkan11Properties
p Ptr PhysicalDeviceVulkan11Properties
-> Int -> Ptr SubgroupFeatureFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 72 :: Ptr SubgroupFeatureFlags))
    Bool32
subgroupQuadOperationsInAllStages <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan11Properties
p Ptr PhysicalDeviceVulkan11Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 76 :: Ptr Bool32))
    PointClippingBehavior
pointClippingBehavior <- Ptr PointClippingBehavior -> IO PointClippingBehavior
forall a. Storable a => Ptr a -> IO a
peek @PointClippingBehavior ((Ptr PhysicalDeviceVulkan11Properties
p Ptr PhysicalDeviceVulkan11Properties
-> Int -> Ptr PointClippingBehavior
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 80 :: Ptr PointClippingBehavior))
    Word32
maxMultiviewViewCount <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceVulkan11Properties
p Ptr PhysicalDeviceVulkan11Properties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 84 :: Ptr Word32))
    Word32
maxMultiviewInstanceIndex <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceVulkan11Properties
p Ptr PhysicalDeviceVulkan11Properties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 88 :: Ptr Word32))
    Bool32
protectedNoFault <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan11Properties
p Ptr PhysicalDeviceVulkan11Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 92 :: Ptr Bool32))
    Word32
maxPerSetDescriptors <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceVulkan11Properties
p Ptr PhysicalDeviceVulkan11Properties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 96 :: Ptr Word32))
    DeviceSize
maxMemoryAllocationSize <- Ptr DeviceSize -> IO DeviceSize
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr PhysicalDeviceVulkan11Properties
p Ptr PhysicalDeviceVulkan11Properties -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 104 :: Ptr DeviceSize))
    PhysicalDeviceVulkan11Properties
-> IO PhysicalDeviceVulkan11Properties
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDeviceVulkan11Properties
 -> IO PhysicalDeviceVulkan11Properties)
-> PhysicalDeviceVulkan11Properties
-> IO PhysicalDeviceVulkan11Properties
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
_ = 112
  alignment :: PhysicalDeviceVulkan11Properties -> Int
alignment ~PhysicalDeviceVulkan11Properties
_ = 8
  peek :: Ptr PhysicalDeviceVulkan11Properties
-> IO PhysicalDeviceVulkan11Properties
peek = Ptr PhysicalDeviceVulkan11Properties
-> IO PhysicalDeviceVulkan11Properties
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: Ptr PhysicalDeviceVulkan11Properties
-> PhysicalDeviceVulkan11Properties -> IO ()
poke ptr :: Ptr PhysicalDeviceVulkan11Properties
ptr poked :: PhysicalDeviceVulkan11Properties
poked = Ptr PhysicalDeviceVulkan11Properties
-> PhysicalDeviceVulkan11Properties -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceVulkan11Properties
ptr PhysicalDeviceVulkan11Properties
poked (() -> IO ()
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
           ByteString
forall a. Monoid a => a
mempty
           ByteString
forall a. Monoid a => a
mempty
           ByteString
forall a. Monoid a => a
mempty
           Word32
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           ShaderStageFlags
forall a. Zero a => a
zero
           SubgroupFeatureFlags
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           PointClippingBehavior
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           DeviceSize
forall a. Zero a => a
zero


-- | VkPhysicalDeviceVulkan12Features - Structure describing the Vulkan 1.2
-- features that can be supported by an implementation
--
-- = Members
--
-- The members of the 'PhysicalDeviceVulkan12Features' structure describe
-- the following features:
--
-- = Description
--
-- -   @samplerMirrorClampToEdge@ indicates whether the implementation
--     supports the
--     'Vulkan.Core10.Enums.SamplerAddressMode.SAMPLER_ADDRESS_MODE_MIRROR_CLAMP_TO_EDGE'
--     sampler address mode. If this feature is not enabled, the
--     'Vulkan.Core10.Enums.SamplerAddressMode.SAMPLER_ADDRESS_MODE_MIRROR_CLAMP_TO_EDGE'
--     sampler address mode /must/ not be used.
--
-- -   @drawIndirectCount@ indicates whether the implementation supports
--     the
--     'Vulkan.Core12.Promoted_From_VK_KHR_draw_indirect_count.cmdDrawIndirectCount'
--     and
--     'Vulkan.Core12.Promoted_From_VK_KHR_draw_indirect_count.cmdDrawIndexedIndirectCount'
--     functions. If this feature is not enabled, these functions /must/
--     not be used.
--
-- -   @storageBuffer8BitAccess@ indicates whether objects in the
--     @StorageBuffer@ or @PhysicalStorageBuffer@ storage class with the
--     @Block@ decoration /can/ have 8-bit integer members. If this feature
--     is not enabled, 8-bit integer members /must/ not be used in such
--     objects. This also indicates whether shader modules /can/ declare
--     the @StorageBuffer8BitAccess@ capability.
--
-- -   @uniformAndStorageBuffer8BitAccess@ indicates whether objects in the
--     @Uniform@ storage class with the @Block@ decoration and in the
--     @StorageBuffer@ or @PhysicalStorageBuffer@ storage class with the
--     same decoration /can/ have 8-bit integer members. If this feature is
--     not enabled, 8-bit integer members /must/ not be used in such
--     objects. This also indicates whether shader modules /can/ declare
--     the @UniformAndStorageBuffer8BitAccess@ capability.
--
-- -   @storagePushConstant8@ indicates whether objects in the
--     @PushConstant@ storage class /can/ have 8-bit integer members. If
--     this feature is not enabled, 8-bit integer members /must/ not be
--     used in such objects. This also indicates whether shader modules
--     /can/ declare the @StoragePushConstant8@ capability.
--
-- -   @shaderBufferInt64Atomics@ indicates whether shaders /can/ perform
--     64-bit unsigned and signed integer atomic operations on buffers.
--
-- -   @shaderSharedInt64Atomics@ indicates whether shaders /can/ perform
--     64-bit unsigned and signed integer atomic operations on shared
--     memory.
--
-- -   @shaderFloat16@ indicates whether 16-bit floats (halfs) are
--     supported in shader code. This also indicates whether shader modules
--     /can/ declare the @Float16@ capability. However, this only enables a
--     subset of the storage classes that SPIR-V allows for the @Float16@
--     SPIR-V capability: Declaring and using 16-bit floats in the
--     @Private@, @Workgroup@, and @Function@ storage classes is enabled,
--     while declaring them in the interface storage classes (e.g.,
--     @UniformConstant@, @Uniform@, @StorageBuffer@, @Input@, @Output@,
--     and @PushConstant@) is not enabled.
--
-- -   @shaderInt8@ indicates whether 8-bit integers (signed and unsigned)
--     are supported in shader code. This also indicates whether shader
--     modules /can/ declare the @Int8@ capability. However, this only
--     enables a subset of the storage classes that SPIR-V allows for the
--     @Int8@ SPIR-V capability: Declaring and using 8-bit integers in the
--     @Private@, @Workgroup@, and @Function@ storage classes is enabled,
--     while declaring them in the interface storage classes (e.g.,
--     @UniformConstant@, @Uniform@, @StorageBuffer@, @Input@, @Output@,
--     and @PushConstant@) is not enabled.
--
-- -   @descriptorIndexing@ indicates whether the implementation supports
--     the minimum set of descriptor indexing features as described in the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-requirements Feature Requirements>
--     section. Enabling the @descriptorIndexing@ member when
--     'Vulkan.Core10.Device.createDevice' is called does not imply the
--     other minimum descriptor indexing features are also enabled. Those
--     other descriptor indexing features /must/ be enabled individually as
--     needed by the application.
--
-- -   @shaderInputAttachmentArrayDynamicIndexing@ indicates whether arrays
--     of input attachments /can/ be indexed by dynamically uniform integer
--     expressions in shader code. If this feature is not enabled,
--     resources with a descriptor type of
--     'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_INPUT_ATTACHMENT'
--     /must/ be indexed only by constant integral expressions when
--     aggregated into arrays in shader code. This also indicates whether
--     shader modules /can/ declare the
--     @InputAttachmentArrayDynamicIndexing@ capability.
--
-- -   @shaderUniformTexelBufferArrayDynamicIndexing@ indicates whether
--     arrays of uniform texel buffers /can/ be indexed by dynamically
--     uniform integer expressions in shader code. If this feature is not
--     enabled, resources with a descriptor type of
--     'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_UNIFORM_TEXEL_BUFFER'
--     /must/ be indexed only by constant integral expressions when
--     aggregated into arrays in shader code. This also indicates whether
--     shader modules /can/ declare the
--     @UniformTexelBufferArrayDynamicIndexing@ capability.
--
-- -   @shaderStorageTexelBufferArrayDynamicIndexing@ indicates whether
--     arrays of storage texel buffers /can/ be indexed by dynamically
--     uniform integer expressions in shader code. If this feature is not
--     enabled, resources with a descriptor type of
--     'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_STORAGE_TEXEL_BUFFER'
--     /must/ be indexed only by constant integral expressions when
--     aggregated into arrays in shader code. This also indicates whether
--     shader modules /can/ declare the
--     @StorageTexelBufferArrayDynamicIndexing@ capability.
--
-- -   @shaderUniformBufferArrayNonUniformIndexing@ indicates whether
--     arrays of uniform buffers /can/ be indexed by non-uniform integer
--     expressions in shader code. If this feature is not enabled,
--     resources with a descriptor type of
--     'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_UNIFORM_BUFFER'
--     or
--     'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_UNIFORM_BUFFER_DYNAMIC'
--     /must/ not be indexed by non-uniform integer expressions when
--     aggregated into arrays in shader code. This also indicates whether
--     shader modules /can/ declare the
--     @UniformBufferArrayNonUniformIndexing@ capability.
--
-- -   @shaderSampledImageArrayNonUniformIndexing@ indicates whether arrays
--     of samplers or sampled images /can/ be indexed by non-uniform
--     integer expressions in shader code. If this feature is not enabled,
--     resources with a descriptor type of
--     'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_SAMPLER',
--     'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_COMBINED_IMAGE_SAMPLER',
--     or
--     'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_SAMPLED_IMAGE'
--     /must/ not be indexed by non-uniform integer expressions when
--     aggregated into arrays in shader code. This also indicates whether
--     shader modules /can/ declare the
--     @SampledImageArrayNonUniformIndexing@ capability.
--
-- -   @shaderStorageBufferArrayNonUniformIndexing@ indicates whether
--     arrays of storage buffers /can/ be indexed by non-uniform integer
--     expressions in shader code. If this feature is not enabled,
--     resources with a descriptor type of
--     'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_STORAGE_BUFFER'
--     or
--     'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_STORAGE_BUFFER_DYNAMIC'
--     /must/ not be indexed by non-uniform integer expressions when
--     aggregated into arrays in shader code. This also indicates whether
--     shader modules /can/ declare the
--     @StorageBufferArrayNonUniformIndexing@ capability.
--
-- -   @shaderStorageImageArrayNonUniformIndexing@ indicates whether arrays
--     of storage images /can/ be indexed by non-uniform integer
--     expressions in shader code. If this feature is not enabled,
--     resources with a descriptor type of
--     'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_STORAGE_IMAGE'
--     /must/ not be indexed by non-uniform integer expressions when
--     aggregated into arrays in shader code. This also indicates whether
--     shader modules /can/ declare the
--     @StorageImageArrayNonUniformIndexing@ capability.
--
-- -   @shaderInputAttachmentArrayNonUniformIndexing@ indicates whether
--     arrays of input attachments /can/ be indexed by non-uniform integer
--     expressions in shader code. If this feature is not enabled,
--     resources with a descriptor type of
--     'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_INPUT_ATTACHMENT'
--     /must/ not be indexed by non-uniform integer expressions when
--     aggregated into arrays in shader code. This also indicates whether
--     shader modules /can/ declare the
--     @InputAttachmentArrayNonUniformIndexing@ capability.
--
-- -   @shaderUniformTexelBufferArrayNonUniformIndexing@ indicates whether
--     arrays of uniform texel buffers /can/ be indexed by non-uniform
--     integer expressions in shader code. If this feature is not enabled,
--     resources with a descriptor type of
--     'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_UNIFORM_TEXEL_BUFFER'
--     /must/ not be indexed by non-uniform integer expressions when
--     aggregated into arrays in shader code. This also indicates whether
--     shader modules /can/ declare the
--     @UniformTexelBufferArrayNonUniformIndexing@ capability.
--
-- -   @shaderStorageTexelBufferArrayNonUniformIndexing@ indicates whether
--     arrays of storage texel buffers /can/ be indexed by non-uniform
--     integer expressions in shader code. If this feature is not enabled,
--     resources with a descriptor type of
--     'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_STORAGE_TEXEL_BUFFER'
--     /must/ not be indexed by non-uniform integer expressions when
--     aggregated into arrays in shader code. This also indicates whether
--     shader modules /can/ declare the
--     @StorageTexelBufferArrayNonUniformIndexing@ capability.
--
-- -   @descriptorBindingUniformBufferUpdateAfterBind@ indicates whether
--     the implementation supports updating uniform buffer descriptors
--     after a set is bound. If this feature is not enabled,
--     'Vulkan.Core12.Enums.DescriptorBindingFlagBits.DESCRIPTOR_BINDING_UPDATE_AFTER_BIND_BIT'
--     /must/ not be used with
--     'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_UNIFORM_BUFFER'.
--
-- -   @descriptorBindingSampledImageUpdateAfterBind@ indicates whether the
--     implementation supports updating sampled image descriptors after a
--     set is bound. If this feature is not enabled,
--     'Vulkan.Core12.Enums.DescriptorBindingFlagBits.DESCRIPTOR_BINDING_UPDATE_AFTER_BIND_BIT'
--     /must/ not be used with
--     'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_SAMPLER',
--     'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_COMBINED_IMAGE_SAMPLER',
--     or
--     'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_SAMPLED_IMAGE'.
--
-- -   @descriptorBindingStorageImageUpdateAfterBind@ indicates whether the
--     implementation supports updating storage image descriptors after a
--     set is bound. If this feature is not enabled,
--     'Vulkan.Core12.Enums.DescriptorBindingFlagBits.DESCRIPTOR_BINDING_UPDATE_AFTER_BIND_BIT'
--     /must/ not be used with
--     'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_STORAGE_IMAGE'.
--
-- -   @descriptorBindingStorageBufferUpdateAfterBind@ indicates whether
--     the implementation supports updating storage buffer descriptors
--     after a set is bound. If this feature is not enabled,
--     'Vulkan.Core12.Enums.DescriptorBindingFlagBits.DESCRIPTOR_BINDING_UPDATE_AFTER_BIND_BIT'
--     /must/ not be used with
--     'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_STORAGE_BUFFER'.
--
-- -   @descriptorBindingUniformTexelBufferUpdateAfterBind@ indicates
--     whether the implementation supports updating uniform texel buffer
--     descriptors after a set is bound. If this feature is not enabled,
--     'Vulkan.Core12.Enums.DescriptorBindingFlagBits.DESCRIPTOR_BINDING_UPDATE_AFTER_BIND_BIT'
--     /must/ not be used with
--     'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_UNIFORM_TEXEL_BUFFER'.
--
-- -   @descriptorBindingStorageTexelBufferUpdateAfterBind@ indicates
--     whether the implementation supports updating storage texel buffer
--     descriptors after a set is bound. If this feature is not enabled,
--     'Vulkan.Core12.Enums.DescriptorBindingFlagBits.DESCRIPTOR_BINDING_UPDATE_AFTER_BIND_BIT'
--     /must/ not be used with
--     'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_STORAGE_TEXEL_BUFFER'.
--
-- -   @descriptorBindingUpdateUnusedWhilePending@ indicates whether the
--     implementation supports updating descriptors while the set is in
--     use. If this feature is not enabled,
--     'Vulkan.Core12.Enums.DescriptorBindingFlagBits.DESCRIPTOR_BINDING_UPDATE_UNUSED_WHILE_PENDING_BIT'
--     /must/ not be used.
--
-- -   @descriptorBindingPartiallyBound@ indicates whether the
--     implementation supports statically using a descriptor set binding in
--     which some descriptors are not valid. If this feature is not
--     enabled,
--     'Vulkan.Core12.Enums.DescriptorBindingFlagBits.DESCRIPTOR_BINDING_PARTIALLY_BOUND_BIT'
--     /must/ not be used.
--
-- -   @descriptorBindingVariableDescriptorCount@ indicates whether the
--     implementation supports descriptor sets with a variable-sized last
--     binding. If this feature is not enabled,
--     'Vulkan.Core12.Enums.DescriptorBindingFlagBits.DESCRIPTOR_BINDING_VARIABLE_DESCRIPTOR_COUNT_BIT'
--     /must/ not be used.
--
-- -   @runtimeDescriptorArray@ indicates whether the implementation
--     supports the SPIR-V @RuntimeDescriptorArray@ capability. If this
--     feature is not enabled, descriptors /must/ not be declared in
--     runtime arrays.
--
-- -   @samplerFilterMinmax@ indicates whether the implementation supports
--     a minimum set of required formats supporting min\/max filtering as
--     defined by the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-filterMinmaxSingleComponentFormats-minimum-requirements filterMinmaxSingleComponentFormats>
--     property minimum requirements. If this feature is not enabled, then
--     no 'Vulkan.Core10.Sampler.SamplerCreateInfo' @pNext@ chain can
--     include a
--     'Vulkan.Core12.Promoted_From_VK_EXT_sampler_filter_minmax.SamplerReductionModeCreateInfo'
--     structure.
--
-- -   @scalarBlockLayout@ indicates that the implementation supports the
--     layout of resource blocks in shaders using
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#interfaces-alignment-requirements scalar alignment>.
--
-- -   @imagelessFramebuffer@ indicates that the implementation supports
--     specifying the image view for attachments at render pass begin time
--     via
--     'Vulkan.Core12.Promoted_From_VK_KHR_imageless_framebuffer.RenderPassAttachmentBeginInfo'.
--
-- -   @uniformBufferStandardLayout@ indicates that the implementation
--     supports the same layouts for uniform buffers as for storage and
--     other kinds of buffers. See
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#interfaces-resources-standard-layout Standard Buffer Layout>.
--
-- -   @shaderSubgroupExtendedTypes@ is a boolean that specifies whether
--     subgroup operations can use 8-bit integer, 16-bit integer, 64-bit
--     integer, 16-bit floating-point, and vectors of these types in
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#shaders-group-operations group operations>
--     with
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#shaders-scope-subgroup subgroup scope>if
--     the implementation supports the types.
--
-- -   @separateDepthStencilLayouts@ indicates whether the implementation
--     supports a 'Vulkan.Core10.OtherTypes.ImageMemoryBarrier' for a
--     depth\/stencil image with only one of
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_DEPTH_BIT' or
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_STENCIL_BIT'
--     set, and whether
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_ATTACHMENT_OPTIMAL',
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_READ_ONLY_OPTIMAL',
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_STENCIL_ATTACHMENT_OPTIMAL',
--     or
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_STENCIL_READ_ONLY_OPTIMAL'
--     can be used.
--
-- -   @hostQueryReset@ indicates that the implementation supports
--     resetting queries from the host with
--     'Vulkan.Core12.Promoted_From_VK_EXT_host_query_reset.resetQueryPool'.
--
-- -   @timelineSemaphore@ indicates whether semaphores created with a
--     'Vulkan.Core12.Enums.SemaphoreType.SemaphoreType' of
--     'Vulkan.Core12.Enums.SemaphoreType.SEMAPHORE_TYPE_TIMELINE' are
--     supported.
--
-- -   @bufferDeviceAddress@ indicates that the implementation supports
--     accessing buffer memory in shaders as storage buffers via an address
--     queried from
--     'Vulkan.Core12.Promoted_From_VK_KHR_buffer_device_address.getBufferDeviceAddress'.
--
-- -   @bufferDeviceAddressCaptureReplay@ indicates that the implementation
--     supports saving and reusing buffer and device addresses, e.g. for
--     trace capture and replay.
--
-- -   @bufferDeviceAddressMultiDevice@ indicates that the implementation
--     supports the @bufferDeviceAddress@ and @rayTracing@ features for
--     logical devices created with multiple physical devices. If this
--     feature is not supported, buffer and acceleration structure
--     addresses /must/ not be queried on a logical device created with
--     more than one physical device.
--
-- -   @vulkanMemoryModel@ indicates whether the Vulkan Memory Model is
--     supported, as defined in
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#memory-model Vulkan Memory Model>.
--     This also indicates whether shader modules /can/ declare the
--     @VulkanMemoryModel@ capability.
--
-- -   @vulkanMemoryModelDeviceScope@ indicates whether the Vulkan Memory
--     Model can use 'Vulkan.Core10.Handles.Device' scope synchronization.
--     This also indicates whether shader modules /can/ declare the
--     @VulkanMemoryModelDeviceScope@ capability.
--
-- -   @vulkanMemoryModelAvailabilityVisibilityChains@ indicates whether
--     the Vulkan Memory Model can use
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#memory-model-availability-visibility availability and visibility chains>
--     with more than one element.
--
-- -   @shaderOutputViewportIndex@ indicates whether the implementation
--     supports the @ShaderViewportIndex@ SPIR-V capability enabling
--     variables decorated with the @ViewportIndex@ built-in to be exported
--     from vertex or tessellation evaluation shaders. If this feature is
--     not enabled, the @ViewportIndex@ built-in decoration /must/ not be
--     used on outputs in vertex or tessellation evaluation shaders.
--
-- -   @shaderOutputLayer@ indicates whether the implementation supports
--     the @ShaderLayer@ SPIR-V capability enabling variables decorated
--     with the @Layer@ built-in to be exported from vertex or tessellation
--     evaluation shaders. If this feature is not enabled, the @Layer@
--     built-in decoration /must/ not be used on outputs in vertex or
--     tessellation evaluation shaders.
--
-- -   If @subgroupBroadcastDynamicId@ is
--     'Vulkan.Core10.FundamentalTypes.TRUE', the “Id” operand of
--     @OpGroupNonUniformBroadcast@ /can/ be dynamically uniform within a
--     subgroup, and the “Index” operand of
--     @OpGroupNonUniformQuadBroadcast@ /can/ be dynamically uniform within
--     the derivative group. If it is
--     'Vulkan.Core10.FundamentalTypes.FALSE', these operands /must/ be
--     constants.
--
-- If the 'PhysicalDeviceVulkan12Features' structure is included in the
-- @pNext@ chain of
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceFeatures2',
-- it is filled with values indicating whether each feature is supported.
-- 'PhysicalDeviceVulkan12Features' /can/ also be used in the @pNext@ chain
-- of 'Vulkan.Core10.Device.DeviceCreateInfo' to enable the features.
--
-- == Valid Usage (Implicit)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PHYSICAL_DEVICE_VULKAN_1_2_FEATURES'
--
-- = See Also
--
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDeviceVulkan12Features = PhysicalDeviceVulkan12Features
  { -- No documentation found for Nested "VkPhysicalDeviceVulkan12Features" "samplerMirrorClampToEdge"
    PhysicalDeviceVulkan12Features -> Bool
samplerMirrorClampToEdge :: Bool
  , -- No documentation found for Nested "VkPhysicalDeviceVulkan12Features" "drawIndirectCount"
    PhysicalDeviceVulkan12Features -> Bool
drawIndirectCount :: Bool
  , -- No documentation found for Nested "VkPhysicalDeviceVulkan12Features" "storageBuffer8BitAccess"
    PhysicalDeviceVulkan12Features -> Bool
storageBuffer8BitAccess :: Bool
  , -- No documentation found for Nested "VkPhysicalDeviceVulkan12Features" "uniformAndStorageBuffer8BitAccess"
    PhysicalDeviceVulkan12Features -> Bool
uniformAndStorageBuffer8BitAccess :: Bool
  , -- No documentation found for Nested "VkPhysicalDeviceVulkan12Features" "storagePushConstant8"
    PhysicalDeviceVulkan12Features -> Bool
storagePushConstant8 :: Bool
  , -- No documentation found for Nested "VkPhysicalDeviceVulkan12Features" "shaderBufferInt64Atomics"
    PhysicalDeviceVulkan12Features -> Bool
shaderBufferInt64Atomics :: Bool
  , -- No documentation found for Nested "VkPhysicalDeviceVulkan12Features" "shaderSharedInt64Atomics"
    PhysicalDeviceVulkan12Features -> Bool
shaderSharedInt64Atomics :: Bool
  , -- No documentation found for Nested "VkPhysicalDeviceVulkan12Features" "shaderFloat16"
    PhysicalDeviceVulkan12Features -> Bool
shaderFloat16 :: Bool
  , -- No documentation found for Nested "VkPhysicalDeviceVulkan12Features" "shaderInt8"
    PhysicalDeviceVulkan12Features -> Bool
shaderInt8 :: Bool
  , -- No documentation found for Nested "VkPhysicalDeviceVulkan12Features" "descriptorIndexing"
    PhysicalDeviceVulkan12Features -> Bool
descriptorIndexing :: Bool
  , -- No documentation found for Nested "VkPhysicalDeviceVulkan12Features" "shaderInputAttachmentArrayDynamicIndexing"
    PhysicalDeviceVulkan12Features -> Bool
shaderInputAttachmentArrayDynamicIndexing :: Bool
  , -- No documentation found for Nested "VkPhysicalDeviceVulkan12Features" "shaderUniformTexelBufferArrayDynamicIndexing"
    PhysicalDeviceVulkan12Features -> Bool
shaderUniformTexelBufferArrayDynamicIndexing :: Bool
  , -- No documentation found for Nested "VkPhysicalDeviceVulkan12Features" "shaderStorageTexelBufferArrayDynamicIndexing"
    PhysicalDeviceVulkan12Features -> Bool
shaderStorageTexelBufferArrayDynamicIndexing :: Bool
  , -- No documentation found for Nested "VkPhysicalDeviceVulkan12Features" "shaderUniformBufferArrayNonUniformIndexing"
    PhysicalDeviceVulkan12Features -> Bool
shaderUniformBufferArrayNonUniformIndexing :: Bool
  , -- No documentation found for Nested "VkPhysicalDeviceVulkan12Features" "shaderSampledImageArrayNonUniformIndexing"
    PhysicalDeviceVulkan12Features -> Bool
shaderSampledImageArrayNonUniformIndexing :: Bool
  , -- No documentation found for Nested "VkPhysicalDeviceVulkan12Features" "shaderStorageBufferArrayNonUniformIndexing"
    PhysicalDeviceVulkan12Features -> Bool
shaderStorageBufferArrayNonUniformIndexing :: Bool
  , -- No documentation found for Nested "VkPhysicalDeviceVulkan12Features" "shaderStorageImageArrayNonUniformIndexing"
    PhysicalDeviceVulkan12Features -> Bool
shaderStorageImageArrayNonUniformIndexing :: Bool
  , -- No documentation found for Nested "VkPhysicalDeviceVulkan12Features" "shaderInputAttachmentArrayNonUniformIndexing"
    PhysicalDeviceVulkan12Features -> Bool
shaderInputAttachmentArrayNonUniformIndexing :: Bool
  , -- No documentation found for Nested "VkPhysicalDeviceVulkan12Features" "shaderUniformTexelBufferArrayNonUniformIndexing"
    PhysicalDeviceVulkan12Features -> Bool
shaderUniformTexelBufferArrayNonUniformIndexing :: Bool
  , -- No documentation found for Nested "VkPhysicalDeviceVulkan12Features" "shaderStorageTexelBufferArrayNonUniformIndexing"
    PhysicalDeviceVulkan12Features -> Bool
shaderStorageTexelBufferArrayNonUniformIndexing :: Bool
  , -- No documentation found for Nested "VkPhysicalDeviceVulkan12Features" "descriptorBindingUniformBufferUpdateAfterBind"
    PhysicalDeviceVulkan12Features -> Bool
descriptorBindingUniformBufferUpdateAfterBind :: Bool
  , -- No documentation found for Nested "VkPhysicalDeviceVulkan12Features" "descriptorBindingSampledImageUpdateAfterBind"
    PhysicalDeviceVulkan12Features -> Bool
descriptorBindingSampledImageUpdateAfterBind :: Bool
  , -- No documentation found for Nested "VkPhysicalDeviceVulkan12Features" "descriptorBindingStorageImageUpdateAfterBind"
    PhysicalDeviceVulkan12Features -> Bool
descriptorBindingStorageImageUpdateAfterBind :: Bool
  , -- No documentation found for Nested "VkPhysicalDeviceVulkan12Features" "descriptorBindingStorageBufferUpdateAfterBind"
    PhysicalDeviceVulkan12Features -> Bool
descriptorBindingStorageBufferUpdateAfterBind :: Bool
  , -- No documentation found for Nested "VkPhysicalDeviceVulkan12Features" "descriptorBindingUniformTexelBufferUpdateAfterBind"
    PhysicalDeviceVulkan12Features -> Bool
descriptorBindingUniformTexelBufferUpdateAfterBind :: Bool
  , -- No documentation found for Nested "VkPhysicalDeviceVulkan12Features" "descriptorBindingStorageTexelBufferUpdateAfterBind"
    PhysicalDeviceVulkan12Features -> Bool
descriptorBindingStorageTexelBufferUpdateAfterBind :: Bool
  , -- No documentation found for Nested "VkPhysicalDeviceVulkan12Features" "descriptorBindingUpdateUnusedWhilePending"
    PhysicalDeviceVulkan12Features -> Bool
descriptorBindingUpdateUnusedWhilePending :: Bool
  , -- No documentation found for Nested "VkPhysicalDeviceVulkan12Features" "descriptorBindingPartiallyBound"
    PhysicalDeviceVulkan12Features -> Bool
descriptorBindingPartiallyBound :: Bool
  , -- No documentation found for Nested "VkPhysicalDeviceVulkan12Features" "descriptorBindingVariableDescriptorCount"
    PhysicalDeviceVulkan12Features -> Bool
descriptorBindingVariableDescriptorCount :: Bool
  , -- No documentation found for Nested "VkPhysicalDeviceVulkan12Features" "runtimeDescriptorArray"
    PhysicalDeviceVulkan12Features -> Bool
runtimeDescriptorArray :: Bool
  , -- No documentation found for Nested "VkPhysicalDeviceVulkan12Features" "samplerFilterMinmax"
    PhysicalDeviceVulkan12Features -> Bool
samplerFilterMinmax :: Bool
  , -- No documentation found for Nested "VkPhysicalDeviceVulkan12Features" "scalarBlockLayout"
    PhysicalDeviceVulkan12Features -> Bool
scalarBlockLayout :: Bool
  , -- No documentation found for Nested "VkPhysicalDeviceVulkan12Features" "imagelessFramebuffer"
    PhysicalDeviceVulkan12Features -> Bool
imagelessFramebuffer :: Bool
  , -- No documentation found for Nested "VkPhysicalDeviceVulkan12Features" "uniformBufferStandardLayout"
    PhysicalDeviceVulkan12Features -> Bool
uniformBufferStandardLayout :: Bool
  , -- No documentation found for Nested "VkPhysicalDeviceVulkan12Features" "shaderSubgroupExtendedTypes"
    PhysicalDeviceVulkan12Features -> Bool
shaderSubgroupExtendedTypes :: Bool
  , -- No documentation found for Nested "VkPhysicalDeviceVulkan12Features" "separateDepthStencilLayouts"
    PhysicalDeviceVulkan12Features -> Bool
separateDepthStencilLayouts :: Bool
  , -- No documentation found for Nested "VkPhysicalDeviceVulkan12Features" "hostQueryReset"
    PhysicalDeviceVulkan12Features -> Bool
hostQueryReset :: Bool
  , -- No documentation found for Nested "VkPhysicalDeviceVulkan12Features" "timelineSemaphore"
    PhysicalDeviceVulkan12Features -> Bool
timelineSemaphore :: Bool
  , -- No documentation found for Nested "VkPhysicalDeviceVulkan12Features" "bufferDeviceAddress"
    PhysicalDeviceVulkan12Features -> Bool
bufferDeviceAddress :: Bool
  , -- No documentation found for Nested "VkPhysicalDeviceVulkan12Features" "bufferDeviceAddressCaptureReplay"
    PhysicalDeviceVulkan12Features -> Bool
bufferDeviceAddressCaptureReplay :: Bool
  , -- No documentation found for Nested "VkPhysicalDeviceVulkan12Features" "bufferDeviceAddressMultiDevice"
    PhysicalDeviceVulkan12Features -> Bool
bufferDeviceAddressMultiDevice :: Bool
  , -- No documentation found for Nested "VkPhysicalDeviceVulkan12Features" "vulkanMemoryModel"
    PhysicalDeviceVulkan12Features -> Bool
vulkanMemoryModel :: Bool
  , -- No documentation found for Nested "VkPhysicalDeviceVulkan12Features" "vulkanMemoryModelDeviceScope"
    PhysicalDeviceVulkan12Features -> Bool
vulkanMemoryModelDeviceScope :: Bool
  , -- No documentation found for Nested "VkPhysicalDeviceVulkan12Features" "vulkanMemoryModelAvailabilityVisibilityChains"
    PhysicalDeviceVulkan12Features -> Bool
vulkanMemoryModelAvailabilityVisibilityChains :: Bool
  , -- No documentation found for Nested "VkPhysicalDeviceVulkan12Features" "shaderOutputViewportIndex"
    PhysicalDeviceVulkan12Features -> Bool
shaderOutputViewportIndex :: Bool
  , -- No documentation found for Nested "VkPhysicalDeviceVulkan12Features" "shaderOutputLayer"
    PhysicalDeviceVulkan12Features -> Bool
shaderOutputLayer :: Bool
  , -- No documentation found for Nested "VkPhysicalDeviceVulkan12Features" "subgroupBroadcastDynamicId"
    PhysicalDeviceVulkan12Features -> Bool
subgroupBroadcastDynamicId :: Bool
  }
  deriving (Typeable, PhysicalDeviceVulkan12Features
-> PhysicalDeviceVulkan12Features -> Bool
(PhysicalDeviceVulkan12Features
 -> PhysicalDeviceVulkan12Features -> Bool)
-> (PhysicalDeviceVulkan12Features
    -> PhysicalDeviceVulkan12Features -> Bool)
-> Eq PhysicalDeviceVulkan12Features
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 :: PhysicalDeviceVulkan12Features
-> (Ptr PhysicalDeviceVulkan12Features -> IO b) -> IO b
withCStruct x :: PhysicalDeviceVulkan12Features
x f :: Ptr PhysicalDeviceVulkan12Features -> IO b
f = Int -> Int -> (Ptr PhysicalDeviceVulkan12Features -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 208 8 ((Ptr PhysicalDeviceVulkan12Features -> IO b) -> IO b)
-> (Ptr PhysicalDeviceVulkan12Features -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr PhysicalDeviceVulkan12Features
p -> Ptr PhysicalDeviceVulkan12Features
-> PhysicalDeviceVulkan12Features -> IO b -> IO b
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 :: Ptr PhysicalDeviceVulkan12Features
-> PhysicalDeviceVulkan12Features -> IO b -> IO b
pokeCStruct p :: Ptr PhysicalDeviceVulkan12Features
p PhysicalDeviceVulkan12Features{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_VULKAN_1_2_FEATURES)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
samplerMirrorClampToEdge))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
drawIndirectCount))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
storageBuffer8BitAccess))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
uniformAndStorageBuffer8BitAccess))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
storagePushConstant8))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 36 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderBufferInt64Atomics))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderSharedInt64Atomics))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 44 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderFloat16))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderInt8))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 52 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
descriptorIndexing))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderInputAttachmentArrayDynamicIndexing))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 60 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderUniformTexelBufferArrayDynamicIndexing))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderStorageTexelBufferArrayDynamicIndexing))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 68 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderUniformBufferArrayNonUniformIndexing))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 72 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderSampledImageArrayNonUniformIndexing))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 76 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderStorageBufferArrayNonUniformIndexing))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 80 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderStorageImageArrayNonUniformIndexing))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 84 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderInputAttachmentArrayNonUniformIndexing))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 88 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderUniformTexelBufferArrayNonUniformIndexing))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 92 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderStorageTexelBufferArrayNonUniformIndexing))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 96 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
descriptorBindingUniformBufferUpdateAfterBind))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 100 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
descriptorBindingSampledImageUpdateAfterBind))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 104 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
descriptorBindingStorageImageUpdateAfterBind))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 108 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
descriptorBindingStorageBufferUpdateAfterBind))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 112 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
descriptorBindingUniformTexelBufferUpdateAfterBind))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 116 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
descriptorBindingStorageTexelBufferUpdateAfterBind))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 120 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
descriptorBindingUpdateUnusedWhilePending))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 124 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
descriptorBindingPartiallyBound))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 128 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
descriptorBindingVariableDescriptorCount))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 132 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
runtimeDescriptorArray))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 136 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
samplerFilterMinmax))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 140 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
scalarBlockLayout))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 144 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
imagelessFramebuffer))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 148 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
uniformBufferStandardLayout))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 152 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderSubgroupExtendedTypes))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 156 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
separateDepthStencilLayouts))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 160 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
hostQueryReset))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 164 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
timelineSemaphore))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 168 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
bufferDeviceAddress))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 172 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
bufferDeviceAddressCaptureReplay))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 176 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
bufferDeviceAddressMultiDevice))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 180 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
vulkanMemoryModel))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 184 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
vulkanMemoryModelDeviceScope))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 188 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
vulkanMemoryModelAvailabilityVisibilityChains))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 192 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderOutputViewportIndex))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 196 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderOutputLayer))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 200 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
subgroupBroadcastDynamicId))
    IO b
f
  cStructSize :: Int
cStructSize = 208
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr PhysicalDeviceVulkan12Features -> IO b -> IO b
pokeZeroCStruct p :: Ptr PhysicalDeviceVulkan12Features
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_VULKAN_1_2_FEATURES)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 36 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 44 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 52 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 60 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 68 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 72 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 76 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 80 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 84 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 88 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 92 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 96 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 100 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 104 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 108 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 112 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 116 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 120 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 124 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 128 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 132 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 136 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 140 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 144 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 148 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 152 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 156 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 160 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 164 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 168 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 172 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 176 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 180 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 184 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 188 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 192 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 196 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 200 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    IO b
f

instance FromCStruct PhysicalDeviceVulkan12Features where
  peekCStruct :: Ptr PhysicalDeviceVulkan12Features
-> IO PhysicalDeviceVulkan12Features
peekCStruct p :: Ptr PhysicalDeviceVulkan12Features
p = do
    Bool32
samplerMirrorClampToEdge <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32))
    Bool32
drawIndirectCount <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Bool32))
    Bool32
storageBuffer8BitAccess <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Bool32))
    Bool32
uniformAndStorageBuffer8BitAccess <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr Bool32))
    Bool32
storagePushConstant8 <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Bool32))
    Bool32
shaderBufferInt64Atomics <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 36 :: Ptr Bool32))
    Bool32
shaderSharedInt64Atomics <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr Bool32))
    Bool32
shaderFloat16 <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 44 :: Ptr Bool32))
    Bool32
shaderInt8 <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr Bool32))
    Bool32
descriptorIndexing <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 52 :: Ptr Bool32))
    Bool32
shaderInputAttachmentArrayDynamicIndexing <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr Bool32))
    Bool32
shaderUniformTexelBufferArrayDynamicIndexing <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 60 :: Ptr Bool32))
    Bool32
shaderStorageTexelBufferArrayDynamicIndexing <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64 :: Ptr Bool32))
    Bool32
shaderUniformBufferArrayNonUniformIndexing <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 68 :: Ptr Bool32))
    Bool32
shaderSampledImageArrayNonUniformIndexing <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 72 :: Ptr Bool32))
    Bool32
shaderStorageBufferArrayNonUniformIndexing <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 76 :: Ptr Bool32))
    Bool32
shaderStorageImageArrayNonUniformIndexing <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 80 :: Ptr Bool32))
    Bool32
shaderInputAttachmentArrayNonUniformIndexing <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 84 :: Ptr Bool32))
    Bool32
shaderUniformTexelBufferArrayNonUniformIndexing <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 88 :: Ptr Bool32))
    Bool32
shaderStorageTexelBufferArrayNonUniformIndexing <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 92 :: Ptr Bool32))
    Bool32
descriptorBindingUniformBufferUpdateAfterBind <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 96 :: Ptr Bool32))
    Bool32
descriptorBindingSampledImageUpdateAfterBind <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 100 :: Ptr Bool32))
    Bool32
descriptorBindingStorageImageUpdateAfterBind <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 104 :: Ptr Bool32))
    Bool32
descriptorBindingStorageBufferUpdateAfterBind <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 108 :: Ptr Bool32))
    Bool32
descriptorBindingUniformTexelBufferUpdateAfterBind <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 112 :: Ptr Bool32))
    Bool32
descriptorBindingStorageTexelBufferUpdateAfterBind <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 116 :: Ptr Bool32))
    Bool32
descriptorBindingUpdateUnusedWhilePending <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 120 :: Ptr Bool32))
    Bool32
descriptorBindingPartiallyBound <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 124 :: Ptr Bool32))
    Bool32
descriptorBindingVariableDescriptorCount <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 128 :: Ptr Bool32))
    Bool32
runtimeDescriptorArray <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 132 :: Ptr Bool32))
    Bool32
samplerFilterMinmax <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 136 :: Ptr Bool32))
    Bool32
scalarBlockLayout <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 140 :: Ptr Bool32))
    Bool32
imagelessFramebuffer <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 144 :: Ptr Bool32))
    Bool32
uniformBufferStandardLayout <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 148 :: Ptr Bool32))
    Bool32
shaderSubgroupExtendedTypes <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 152 :: Ptr Bool32))
    Bool32
separateDepthStencilLayouts <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 156 :: Ptr Bool32))
    Bool32
hostQueryReset <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 160 :: Ptr Bool32))
    Bool32
timelineSemaphore <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 164 :: Ptr Bool32))
    Bool32
bufferDeviceAddress <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 168 :: Ptr Bool32))
    Bool32
bufferDeviceAddressCaptureReplay <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 172 :: Ptr Bool32))
    Bool32
bufferDeviceAddressMultiDevice <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 176 :: Ptr Bool32))
    Bool32
vulkanMemoryModel <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 180 :: Ptr Bool32))
    Bool32
vulkanMemoryModelDeviceScope <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 184 :: Ptr Bool32))
    Bool32
vulkanMemoryModelAvailabilityVisibilityChains <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 188 :: Ptr Bool32))
    Bool32
shaderOutputViewportIndex <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 192 :: Ptr Bool32))
    Bool32
shaderOutputLayer <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 196 :: Ptr Bool32))
    Bool32
subgroupBroadcastDynamicId <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Features
p Ptr PhysicalDeviceVulkan12Features -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 200 :: Ptr Bool32))
    PhysicalDeviceVulkan12Features -> IO PhysicalDeviceVulkan12Features
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDeviceVulkan12Features
 -> IO PhysicalDeviceVulkan12Features)
-> PhysicalDeviceVulkan12Features
-> IO PhysicalDeviceVulkan12Features
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
_ = 208
  alignment :: PhysicalDeviceVulkan12Features -> Int
alignment ~PhysicalDeviceVulkan12Features
_ = 8
  peek :: Ptr PhysicalDeviceVulkan12Features
-> IO PhysicalDeviceVulkan12Features
peek = Ptr PhysicalDeviceVulkan12Features
-> IO PhysicalDeviceVulkan12Features
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: Ptr PhysicalDeviceVulkan12Features
-> PhysicalDeviceVulkan12Features -> IO ()
poke ptr :: Ptr PhysicalDeviceVulkan12Features
ptr poked :: PhysicalDeviceVulkan12Features
poked = Ptr PhysicalDeviceVulkan12Features
-> PhysicalDeviceVulkan12Features -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceVulkan12Features
ptr PhysicalDeviceVulkan12Features
poked (() -> IO ()
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
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero


-- | VkPhysicalDeviceVulkan12Properties - Structure specifying physical
-- device properties for functionality promoted to Vulkan 1.2
--
-- = Description
--
-- The members of 'PhysicalDeviceVulkan12Properties' /must/ have the same
-- values as the corresponding members of
-- 'Vulkan.Core12.Promoted_From_VK_KHR_driver_properties.PhysicalDeviceDriverProperties',
-- 'Vulkan.Core12.Promoted_From_VK_KHR_shader_float_controls.PhysicalDeviceFloatControlsProperties',
-- 'Vulkan.Core12.Promoted_From_VK_EXT_descriptor_indexing.PhysicalDeviceDescriptorIndexingProperties',
-- 'Vulkan.Core12.Promoted_From_VK_KHR_depth_stencil_resolve.PhysicalDeviceDepthStencilResolveProperties',
-- 'Vulkan.Core12.Promoted_From_VK_EXT_sampler_filter_minmax.PhysicalDeviceSamplerFilterMinmaxProperties',
-- and
-- 'Vulkan.Core12.Promoted_From_VK_KHR_timeline_semaphore.PhysicalDeviceTimelineSemaphoreProperties'.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core12.Promoted_From_VK_KHR_driver_properties.ConformanceVersion',
-- 'Vulkan.Core12.Enums.DriverId.DriverId',
-- 'Vulkan.Core12.Enums.ResolveModeFlagBits.ResolveModeFlags',
-- 'Vulkan.Core10.Enums.SampleCountFlagBits.SampleCountFlags',
-- 'Vulkan.Core12.Enums.ShaderFloatControlsIndependence.ShaderFloatControlsIndependence',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDeviceVulkan12Properties = PhysicalDeviceVulkan12Properties
  { -- | @driverID@ is a unique identifier for the driver of the physical device.
    PhysicalDeviceVulkan12Properties -> DriverId
driverID :: DriverId
  , -- | @driverName@ is an array of
    -- 'Vulkan.Core10.APIConstants.MAX_DRIVER_NAME_SIZE' @char@ containing a
    -- null-terminated UTF-8 string which is the name of the driver.
    PhysicalDeviceVulkan12Properties -> ByteString
driverName :: ByteString
  , -- | @driverInfo@ is an array of
    -- 'Vulkan.Core10.APIConstants.MAX_DRIVER_INFO_SIZE' @char@ containing a
    -- null-terminated UTF-8 string with additional information about the
    -- driver.
    PhysicalDeviceVulkan12Properties -> ByteString
driverInfo :: ByteString
  , -- | @conformanceVersion@ is the version of the Vulkan conformance test this
    -- driver is conformant against (see
    -- 'Vulkan.Core12.Promoted_From_VK_KHR_driver_properties.ConformanceVersion').
    PhysicalDeviceVulkan12Properties -> ConformanceVersion
conformanceVersion :: ConformanceVersion
  , -- | @denormBehaviorIndependence@ is a
    -- 'Vulkan.Core12.Enums.ShaderFloatControlsIndependence.ShaderFloatControlsIndependence'
    -- value indicating whether, and how, denorm behavior can be set
    -- independently for different bit widths.
    PhysicalDeviceVulkan12Properties -> ShaderFloatControlsIndependence
denormBehaviorIndependence :: ShaderFloatControlsIndependence
  , -- | @roundingModeIndependence@ is a
    -- 'Vulkan.Core12.Enums.ShaderFloatControlsIndependence.ShaderFloatControlsIndependence'
    -- value indicating whether, and how, rounding modes can be set
    -- independently for different bit widths.
    PhysicalDeviceVulkan12Properties -> ShaderFloatControlsIndependence
roundingModeIndependence :: ShaderFloatControlsIndependence
  , -- | @shaderSignedZeroInfNanPreserveFloat16@ is a boolean value indicating
    -- whether sign of a zero, Nans and \(\pm\infty\) /can/ be preserved in
    -- 16-bit floating-point computations. It also indicates whether the
    -- @SignedZeroInfNanPreserve@ execution mode /can/ be used for 16-bit
    -- floating-point types.
    PhysicalDeviceVulkan12Properties -> Bool
shaderSignedZeroInfNanPreserveFloat16 :: Bool
  , -- | @shaderSignedZeroInfNanPreserveFloat32@ is a boolean value indicating
    -- whether sign of a zero, Nans and \(\pm\infty\) /can/ be preserved in
    -- 32-bit floating-point computations. It also indicates whether the
    -- @SignedZeroInfNanPreserve@ execution mode /can/ be used for 32-bit
    -- floating-point types.
    PhysicalDeviceVulkan12Properties -> Bool
shaderSignedZeroInfNanPreserveFloat32 :: Bool
  , -- | @shaderSignedZeroInfNanPreserveFloat64@ is a boolean value indicating
    -- whether sign of a zero, Nans and \(\pm\infty\) /can/ be preserved in
    -- 64-bit floating-point computations. It also indicates whether the
    -- @SignedZeroInfNanPreserve@ execution mode /can/ be used for 64-bit
    -- floating-point types.
    PhysicalDeviceVulkan12Properties -> Bool
shaderSignedZeroInfNanPreserveFloat64 :: Bool
  , -- | @shaderDenormPreserveFloat16@ is a boolean value indicating whether
    -- denormals /can/ be preserved in 16-bit floating-point computations. It
    -- also indicates whether the @DenormPreserve@ execution mode /can/ be used
    -- for 16-bit floating-point types.
    PhysicalDeviceVulkan12Properties -> Bool
shaderDenormPreserveFloat16 :: Bool
  , -- | @shaderDenormPreserveFloat32@ is a boolean value indicating whether
    -- denormals /can/ be preserved in 32-bit floating-point computations. It
    -- also indicates whether the @DenormPreserve@ execution mode /can/ be used
    -- for 32-bit floating-point types.
    PhysicalDeviceVulkan12Properties -> Bool
shaderDenormPreserveFloat32 :: Bool
  , -- | @shaderDenormPreserveFloat64@ is a boolean value indicating whether
    -- denormals /can/ be preserved in 64-bit floating-point computations. It
    -- also indicates whether the @DenormPreserve@ execution mode /can/ be used
    -- for 64-bit floating-point types.
    PhysicalDeviceVulkan12Properties -> Bool
shaderDenormPreserveFloat64 :: Bool
  , -- | @shaderDenormFlushToZeroFloat16@ is a boolean value indicating whether
    -- denormals /can/ be flushed to zero in 16-bit floating-point
    -- computations. It also indicates whether the @DenormFlushToZero@
    -- execution mode /can/ be used for 16-bit floating-point types.
    PhysicalDeviceVulkan12Properties -> Bool
shaderDenormFlushToZeroFloat16 :: Bool
  , -- | @shaderDenormFlushToZeroFloat32@ is a boolean value indicating whether
    -- denormals /can/ be flushed to zero in 32-bit floating-point
    -- computations. It also indicates whether the @DenormFlushToZero@
    -- execution mode /can/ be used for 32-bit floating-point types.
    PhysicalDeviceVulkan12Properties -> Bool
shaderDenormFlushToZeroFloat32 :: Bool
  , -- | @shaderDenormFlushToZeroFloat64@ is a boolean value indicating whether
    -- denormals /can/ be flushed to zero in 64-bit floating-point
    -- computations. It also indicates whether the @DenormFlushToZero@
    -- execution mode /can/ be used for 64-bit floating-point types.
    PhysicalDeviceVulkan12Properties -> Bool
shaderDenormFlushToZeroFloat64 :: Bool
  , -- | @shaderRoundingModeRTEFloat16@ is a boolean value indicating whether an
    -- implementation supports the round-to-nearest-even rounding mode for
    -- 16-bit floating-point arithmetic and conversion instructions. It also
    -- indicates whether the @RoundingModeRTE@ execution mode /can/ be used for
    -- 16-bit floating-point types.
    PhysicalDeviceVulkan12Properties -> Bool
shaderRoundingModeRTEFloat16 :: Bool
  , -- | @shaderRoundingModeRTEFloat32@ is a boolean value indicating whether an
    -- implementation supports the round-to-nearest-even rounding mode for
    -- 32-bit floating-point arithmetic and conversion instructions. It also
    -- indicates whether the @RoundingModeRTE@ execution mode /can/ be used for
    -- 32-bit floating-point types.
    PhysicalDeviceVulkan12Properties -> Bool
shaderRoundingModeRTEFloat32 :: Bool
  , -- | @shaderRoundingModeRTEFloat64@ is a boolean value indicating whether an
    -- implementation supports the round-to-nearest-even rounding mode for
    -- 64-bit floating-point arithmetic and conversion instructions. It also
    -- indicates whether the @RoundingModeRTE@ execution mode /can/ be used for
    -- 64-bit floating-point types.
    PhysicalDeviceVulkan12Properties -> Bool
shaderRoundingModeRTEFloat64 :: Bool
  , -- | @shaderRoundingModeRTZFloat16@ is a boolean value indicating whether an
    -- implementation supports the round-towards-zero rounding mode for 16-bit
    -- floating-point arithmetic and conversion instructions. It also indicates
    -- whether the @RoundingModeRTZ@ execution mode /can/ be used for 16-bit
    -- floating-point types.
    PhysicalDeviceVulkan12Properties -> Bool
shaderRoundingModeRTZFloat16 :: Bool
  , -- | @shaderRoundingModeRTZFloat32@ is a boolean value indicating whether an
    -- implementation supports the round-towards-zero rounding mode for 32-bit
    -- floating-point arithmetic and conversion instructions. It also indicates
    -- whether the @RoundingModeRTZ@ execution mode /can/ be used for 32-bit
    -- floating-point types.
    PhysicalDeviceVulkan12Properties -> Bool
shaderRoundingModeRTZFloat32 :: Bool
  , -- | @shaderRoundingModeRTZFloat64@ is a boolean value indicating whether an
    -- implementation supports the round-towards-zero rounding mode for 64-bit
    -- floating-point arithmetic and conversion instructions. It also indicates
    -- whether the @RoundingModeRTZ@ execution mode /can/ be used for 64-bit
    -- floating-point types.
    PhysicalDeviceVulkan12Properties -> Bool
shaderRoundingModeRTZFloat64 :: Bool
  , -- | @maxUpdateAfterBindDescriptorsInAllPools@ is the maximum number of
    -- descriptors (summed over all descriptor types) that /can/ be created
    -- across all pools that are created with the
    -- 'Vulkan.Core10.Enums.DescriptorPoolCreateFlagBits.DESCRIPTOR_POOL_CREATE_UPDATE_AFTER_BIND_BIT'
    -- bit set. Pool creation /may/ fail when this limit is exceeded, or when
    -- the space this limit represents is unable to satisfy a pool creation due
    -- to fragmentation.
    PhysicalDeviceVulkan12Properties -> Word32
maxUpdateAfterBindDescriptorsInAllPools :: Word32
  , -- | @shaderUniformBufferArrayNonUniformIndexingNative@ is a boolean value
    -- indicating whether uniform buffer descriptors natively support
    -- nonuniform indexing. If this is 'Vulkan.Core10.FundamentalTypes.FALSE',
    -- then a single dynamic instance of an instruction that nonuniformly
    -- indexes an array of uniform buffers /may/ execute multiple times in
    -- order to access all the descriptors.
    PhysicalDeviceVulkan12Properties -> Bool
shaderUniformBufferArrayNonUniformIndexingNative :: Bool
  , -- | @shaderSampledImageArrayNonUniformIndexingNative@ is a boolean value
    -- indicating whether sampler and image descriptors natively support
    -- nonuniform indexing. If this is 'Vulkan.Core10.FundamentalTypes.FALSE',
    -- then a single dynamic instance of an instruction that nonuniformly
    -- indexes an array of samplers or images /may/ execute multiple times in
    -- order to access all the descriptors.
    PhysicalDeviceVulkan12Properties -> Bool
shaderSampledImageArrayNonUniformIndexingNative :: Bool
  , -- | @shaderStorageBufferArrayNonUniformIndexingNative@ is a boolean value
    -- indicating whether storage buffer descriptors natively support
    -- nonuniform indexing. If this is 'Vulkan.Core10.FundamentalTypes.FALSE',
    -- then a single dynamic instance of an instruction that nonuniformly
    -- indexes an array of storage buffers /may/ execute multiple times in
    -- order to access all the descriptors.
    PhysicalDeviceVulkan12Properties -> Bool
shaderStorageBufferArrayNonUniformIndexingNative :: Bool
  , -- | @shaderStorageImageArrayNonUniformIndexingNative@ is a boolean value
    -- indicating whether storage image descriptors natively support nonuniform
    -- indexing. If this is 'Vulkan.Core10.FundamentalTypes.FALSE', then a
    -- single dynamic instance of an instruction that nonuniformly indexes an
    -- array of storage images /may/ execute multiple times in order to access
    -- all the descriptors.
    PhysicalDeviceVulkan12Properties -> Bool
shaderStorageImageArrayNonUniformIndexingNative :: Bool
  , -- | @shaderInputAttachmentArrayNonUniformIndexingNative@ is a boolean value
    -- indicating whether input attachment descriptors natively support
    -- nonuniform indexing. If this is 'Vulkan.Core10.FundamentalTypes.FALSE',
    -- then a single dynamic instance of an instruction that nonuniformly
    -- indexes an array of input attachments /may/ execute multiple times in
    -- order to access all the descriptors.
    PhysicalDeviceVulkan12Properties -> Bool
shaderInputAttachmentArrayNonUniformIndexingNative :: Bool
  , -- | @robustBufferAccessUpdateAfterBind@ is a boolean value indicating
    -- whether
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-robustBufferAccess robustBufferAccess>
    -- /can/ be enabled in a device simultaneously with
    -- @descriptorBindingUniformBufferUpdateAfterBind@,
    -- @descriptorBindingStorageBufferUpdateAfterBind@,
    -- @descriptorBindingUniformTexelBufferUpdateAfterBind@, and\/or
    -- @descriptorBindingStorageTexelBufferUpdateAfterBind@. If this is
    -- 'Vulkan.Core10.FundamentalTypes.FALSE', then either @robustBufferAccess@
    -- /must/ be disabled or all of these update-after-bind features /must/ be
    -- disabled.
    PhysicalDeviceVulkan12Properties -> Bool
robustBufferAccessUpdateAfterBind :: Bool
  , -- | @quadDivergentImplicitLod@ is a boolean value indicating whether
    -- implicit level of detail calculations for image operations have
    -- well-defined results when the image and\/or sampler objects used for the
    -- instruction are not uniform within a quad. See
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#textures-derivative-image-operations Derivative Image Operations>.
    PhysicalDeviceVulkan12Properties -> Bool
quadDivergentImplicitLod :: Bool
  , -- | @maxPerStageDescriptorUpdateAfterBindSamplers@ is similar to
    -- @maxPerStageDescriptorSamplers@ but counts descriptors from descriptor
    -- sets created with or without the
    -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT'
    -- bit set.
    PhysicalDeviceVulkan12Properties -> Word32
maxPerStageDescriptorUpdateAfterBindSamplers :: Word32
  , -- | @maxPerStageDescriptorUpdateAfterBindUniformBuffers@ is similar to
    -- @maxPerStageDescriptorUniformBuffers@ but counts descriptors from
    -- descriptor sets created with or without the
    -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT'
    -- bit set.
    PhysicalDeviceVulkan12Properties -> Word32
maxPerStageDescriptorUpdateAfterBindUniformBuffers :: Word32
  , -- | @maxPerStageDescriptorUpdateAfterBindStorageBuffers@ is similar to
    -- @maxPerStageDescriptorStorageBuffers@ but counts descriptors from
    -- descriptor sets created with or without the
    -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT'
    -- bit set.
    PhysicalDeviceVulkan12Properties -> Word32
maxPerStageDescriptorUpdateAfterBindStorageBuffers :: Word32
  , -- | @maxPerStageDescriptorUpdateAfterBindSampledImages@ is similar to
    -- @maxPerStageDescriptorSampledImages@ but counts descriptors from
    -- descriptor sets created with or without the
    -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT'
    -- bit set.
    PhysicalDeviceVulkan12Properties -> Word32
maxPerStageDescriptorUpdateAfterBindSampledImages :: Word32
  , -- | @maxPerStageDescriptorUpdateAfterBindStorageImages@ is similar to
    -- @maxPerStageDescriptorStorageImages@ but counts descriptors from
    -- descriptor sets created with or without the
    -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT'
    -- bit set.
    PhysicalDeviceVulkan12Properties -> Word32
maxPerStageDescriptorUpdateAfterBindStorageImages :: Word32
  , -- | @maxPerStageDescriptorUpdateAfterBindInputAttachments@ is similar to
    -- @maxPerStageDescriptorInputAttachments@ but counts descriptors from
    -- descriptor sets created with or without the
    -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT'
    -- bit set.
    PhysicalDeviceVulkan12Properties -> Word32
maxPerStageDescriptorUpdateAfterBindInputAttachments :: Word32
  , -- | @maxPerStageUpdateAfterBindResources@ is similar to
    -- @maxPerStageResources@ but counts descriptors from descriptor sets
    -- created with or without the
    -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT'
    -- bit set.
    PhysicalDeviceVulkan12Properties -> Word32
maxPerStageUpdateAfterBindResources :: Word32
  , -- | @maxDescriptorSetUpdateAfterBindSamplers@ is similar to
    -- @maxDescriptorSetSamplers@ but counts descriptors from descriptor sets
    -- created with or without the
    -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT'
    -- bit set.
    PhysicalDeviceVulkan12Properties -> Word32
maxDescriptorSetUpdateAfterBindSamplers :: Word32
  , -- | @maxDescriptorSetUpdateAfterBindUniformBuffers@ is similar to
    -- @maxDescriptorSetUniformBuffers@ but counts descriptors from descriptor
    -- sets created with or without the
    -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT'
    -- bit set.
    PhysicalDeviceVulkan12Properties -> Word32
maxDescriptorSetUpdateAfterBindUniformBuffers :: Word32
  , -- | @maxDescriptorSetUpdateAfterBindUniformBuffersDynamic@ is similar to
    -- @maxDescriptorSetUniformBuffersDynamic@ but counts descriptors from
    -- descriptor sets created with or without the
    -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT'
    -- bit set.
    PhysicalDeviceVulkan12Properties -> Word32
maxDescriptorSetUpdateAfterBindUniformBuffersDynamic :: Word32
  , -- | @maxDescriptorSetUpdateAfterBindStorageBuffers@ is similar to
    -- @maxDescriptorSetStorageBuffers@ but counts descriptors from descriptor
    -- sets created with or without the
    -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT'
    -- bit set.
    PhysicalDeviceVulkan12Properties -> Word32
maxDescriptorSetUpdateAfterBindStorageBuffers :: Word32
  , -- | @maxDescriptorSetUpdateAfterBindStorageBuffersDynamic@ is similar to
    -- @maxDescriptorSetStorageBuffersDynamic@ but counts descriptors from
    -- descriptor sets created with or without the
    -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT'
    -- bit set.
    PhysicalDeviceVulkan12Properties -> Word32
maxDescriptorSetUpdateAfterBindStorageBuffersDynamic :: Word32
  , -- | @maxDescriptorSetUpdateAfterBindSampledImages@ is similar to
    -- @maxDescriptorSetSampledImages@ but counts descriptors from descriptor
    -- sets created with or without the
    -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT'
    -- bit set.
    PhysicalDeviceVulkan12Properties -> Word32
maxDescriptorSetUpdateAfterBindSampledImages :: Word32
  , -- | @maxDescriptorSetUpdateAfterBindStorageImages@ is similar to
    -- @maxDescriptorSetStorageImages@ but counts descriptors from descriptor
    -- sets created with or without the
    -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT'
    -- bit set.
    PhysicalDeviceVulkan12Properties -> Word32
maxDescriptorSetUpdateAfterBindStorageImages :: Word32
  , -- | @maxDescriptorSetUpdateAfterBindInputAttachments@ is similar to
    -- @maxDescriptorSetInputAttachments@ but counts descriptors from
    -- descriptor sets created with or without the
    -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT'
    -- bit set.
    PhysicalDeviceVulkan12Properties -> Word32
maxDescriptorSetUpdateAfterBindInputAttachments :: Word32
  , -- | @supportedDepthResolveModes@ is a bitmask of
    -- 'Vulkan.Core12.Enums.ResolveModeFlagBits.ResolveModeFlagBits' indicating
    -- the set of supported depth resolve modes.
    -- 'Vulkan.Core12.Enums.ResolveModeFlagBits.RESOLVE_MODE_SAMPLE_ZERO_BIT'
    -- /must/ be included in the set but implementations /may/ support
    -- additional modes.
    PhysicalDeviceVulkan12Properties -> ResolveModeFlags
supportedDepthResolveModes :: ResolveModeFlags
  , -- | @supportedStencilResolveModes@ is a bitmask of
    -- 'Vulkan.Core12.Enums.ResolveModeFlagBits.ResolveModeFlagBits' indicating
    -- the set of supported stencil resolve modes.
    -- 'Vulkan.Core12.Enums.ResolveModeFlagBits.RESOLVE_MODE_SAMPLE_ZERO_BIT'
    -- /must/ be included in the set but implementations /may/ support
    -- additional modes.
    -- 'Vulkan.Core12.Enums.ResolveModeFlagBits.RESOLVE_MODE_AVERAGE_BIT'
    -- /must/ not be included in the set.
    PhysicalDeviceVulkan12Properties -> ResolveModeFlags
supportedStencilResolveModes :: ResolveModeFlags
  , -- | @independentResolveNone@ is 'Vulkan.Core10.FundamentalTypes.TRUE' if the
    -- implementation supports setting the depth and stencil resolve modes to
    -- different values when one of those modes is
    -- 'Vulkan.Core12.Enums.ResolveModeFlagBits.RESOLVE_MODE_NONE'. Otherwise
    -- the implementation only supports setting both modes to the same value.
    PhysicalDeviceVulkan12Properties -> Bool
independentResolveNone :: Bool
  , -- | @independentResolve@ is 'Vulkan.Core10.FundamentalTypes.TRUE' if the
    -- implementation supports all combinations of the supported depth and
    -- stencil resolve modes, including setting either depth or stencil resolve
    -- mode to 'Vulkan.Core12.Enums.ResolveModeFlagBits.RESOLVE_MODE_NONE'. An
    -- implementation that supports @independentResolve@ /must/ also support
    -- @independentResolveNone@.
    PhysicalDeviceVulkan12Properties -> Bool
independentResolve :: Bool
  , -- | @filterMinmaxSingleComponentFormats@ is a boolean value indicating
    -- whether a minimum set of required formats support min\/max filtering.
    PhysicalDeviceVulkan12Properties -> Bool
filterMinmaxSingleComponentFormats :: Bool
  , -- | @filterMinmaxImageComponentMapping@ is a boolean value indicating
    -- whether the implementation supports non-identity component mapping of
    -- the image when doing min\/max filtering.
    PhysicalDeviceVulkan12Properties -> Bool
filterMinmaxImageComponentMapping :: Bool
  , -- | @maxTimelineSemaphoreValueDifference@ indicates the maximum difference
    -- allowed by the implementation between the current value of a timeline
    -- semaphore and any pending signal or wait operations.
    PhysicalDeviceVulkan12Properties -> DeviceSize
maxTimelineSemaphoreValueDifference :: Word64
  , -- | @framebufferIntegerColorSampleCounts@ is a bitmask of
    -- 'Vulkan.Core10.Enums.SampleCountFlagBits.SampleCountFlagBits' indicating
    -- the color sample counts that are supported for all framebuffer color
    -- attachments with integer formats.
    PhysicalDeviceVulkan12Properties -> SampleCountFlags
framebufferIntegerColorSampleCounts :: SampleCountFlags
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceVulkan12Properties)
#endif
deriving instance Show PhysicalDeviceVulkan12Properties

instance ToCStruct PhysicalDeviceVulkan12Properties where
  withCStruct :: PhysicalDeviceVulkan12Properties
-> (Ptr PhysicalDeviceVulkan12Properties -> IO b) -> IO b
withCStruct x :: PhysicalDeviceVulkan12Properties
x f :: Ptr PhysicalDeviceVulkan12Properties -> IO b
f = Int
-> Int -> (Ptr PhysicalDeviceVulkan12Properties -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 736 8 ((Ptr PhysicalDeviceVulkan12Properties -> IO b) -> IO b)
-> (Ptr PhysicalDeviceVulkan12Properties -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr PhysicalDeviceVulkan12Properties
p -> Ptr PhysicalDeviceVulkan12Properties
-> PhysicalDeviceVulkan12Properties -> IO b -> IO b
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 :: Ptr PhysicalDeviceVulkan12Properties
-> PhysicalDeviceVulkan12Properties -> IO b -> IO b
pokeCStruct p :: Ptr PhysicalDeviceVulkan12Properties
p PhysicalDeviceVulkan12Properties{..} f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_VULKAN_1_2_PROPERTIES)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr DriverId -> DriverId -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr DriverId
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr DriverId)) (DriverId
driverID)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (FixedArray MAX_DRIVER_NAME_SIZE CChar) -> ByteString -> IO ()
forall (n :: Nat).
KnownNat n =>
Ptr (FixedArray n CChar) -> ByteString -> IO ()
pokeFixedLengthNullTerminatedByteString ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties
-> Int -> Ptr (FixedArray MAX_DRIVER_NAME_SIZE CChar)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr (FixedArray MAX_DRIVER_NAME_SIZE CChar))) (ByteString
driverName)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (FixedArray MAX_DRIVER_NAME_SIZE CChar) -> ByteString -> IO ()
forall (n :: Nat).
KnownNat n =>
Ptr (FixedArray n CChar) -> ByteString -> IO ()
pokeFixedLengthNullTerminatedByteString ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties
-> Int -> Ptr (FixedArray MAX_DRIVER_NAME_SIZE CChar)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 276 :: Ptr (FixedArray MAX_DRIVER_INFO_SIZE CChar))) (ByteString
driverInfo)
    ((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ConformanceVersion -> ConformanceVersion -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties
-> Int -> Ptr ConformanceVersion
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 532 :: Ptr ConformanceVersion)) (ConformanceVersion
conformanceVersion) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ShaderFloatControlsIndependence
-> ShaderFloatControlsIndependence -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties
-> Int -> Ptr ShaderFloatControlsIndependence
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 536 :: Ptr ShaderFloatControlsIndependence)) (ShaderFloatControlsIndependence
denormBehaviorIndependence)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ShaderFloatControlsIndependence
-> ShaderFloatControlsIndependence -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties
-> Int -> Ptr ShaderFloatControlsIndependence
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 540 :: Ptr ShaderFloatControlsIndependence)) (ShaderFloatControlsIndependence
roundingModeIndependence)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 544 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderSignedZeroInfNanPreserveFloat16))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 548 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderSignedZeroInfNanPreserveFloat32))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 552 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderSignedZeroInfNanPreserveFloat64))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 556 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderDenormPreserveFloat16))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 560 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderDenormPreserveFloat32))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 564 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderDenormPreserveFloat64))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 568 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderDenormFlushToZeroFloat16))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 572 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderDenormFlushToZeroFloat32))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 576 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderDenormFlushToZeroFloat64))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 580 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderRoundingModeRTEFloat16))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 584 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderRoundingModeRTEFloat32))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 588 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderRoundingModeRTEFloat64))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 592 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderRoundingModeRTZFloat16))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 596 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderRoundingModeRTZFloat32))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 600 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderRoundingModeRTZFloat64))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 604 :: Ptr Word32)) (Word32
maxUpdateAfterBindDescriptorsInAllPools)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 608 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderUniformBufferArrayNonUniformIndexingNative))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 612 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderSampledImageArrayNonUniformIndexingNative))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 616 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderStorageBufferArrayNonUniformIndexingNative))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 620 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderStorageImageArrayNonUniformIndexingNative))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 624 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderInputAttachmentArrayNonUniformIndexingNative))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 628 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
robustBufferAccessUpdateAfterBind))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 632 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
quadDivergentImplicitLod))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 636 :: Ptr Word32)) (Word32
maxPerStageDescriptorUpdateAfterBindSamplers)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 640 :: Ptr Word32)) (Word32
maxPerStageDescriptorUpdateAfterBindUniformBuffers)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 644 :: Ptr Word32)) (Word32
maxPerStageDescriptorUpdateAfterBindStorageBuffers)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 648 :: Ptr Word32)) (Word32
maxPerStageDescriptorUpdateAfterBindSampledImages)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 652 :: Ptr Word32)) (Word32
maxPerStageDescriptorUpdateAfterBindStorageImages)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 656 :: Ptr Word32)) (Word32
maxPerStageDescriptorUpdateAfterBindInputAttachments)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 660 :: Ptr Word32)) (Word32
maxPerStageUpdateAfterBindResources)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 664 :: Ptr Word32)) (Word32
maxDescriptorSetUpdateAfterBindSamplers)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 668 :: Ptr Word32)) (Word32
maxDescriptorSetUpdateAfterBindUniformBuffers)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 672 :: Ptr Word32)) (Word32
maxDescriptorSetUpdateAfterBindUniformBuffersDynamic)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 676 :: Ptr Word32)) (Word32
maxDescriptorSetUpdateAfterBindStorageBuffers)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 680 :: Ptr Word32)) (Word32
maxDescriptorSetUpdateAfterBindStorageBuffersDynamic)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 684 :: Ptr Word32)) (Word32
maxDescriptorSetUpdateAfterBindSampledImages)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 688 :: Ptr Word32)) (Word32
maxDescriptorSetUpdateAfterBindStorageImages)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 692 :: Ptr Word32)) (Word32
maxDescriptorSetUpdateAfterBindInputAttachments)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ResolveModeFlags -> ResolveModeFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr ResolveModeFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 696 :: Ptr ResolveModeFlags)) (ResolveModeFlags
supportedDepthResolveModes)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ResolveModeFlags -> ResolveModeFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr ResolveModeFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 700 :: Ptr ResolveModeFlags)) (ResolveModeFlags
supportedStencilResolveModes)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 704 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
independentResolveNone))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 708 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
independentResolve))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 712 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
filterMinmaxSingleComponentFormats))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 716 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
filterMinmaxImageComponentMapping))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 720 :: Ptr Word64)) (DeviceSize
maxTimelineSemaphoreValueDifference)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr SampleCountFlags -> SampleCountFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr SampleCountFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 728 :: Ptr SampleCountFlags)) (SampleCountFlags
framebufferIntegerColorSampleCounts)
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
  cStructSize :: Int
cStructSize = 736
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr PhysicalDeviceVulkan12Properties -> IO b -> IO b
pokeZeroCStruct p :: Ptr PhysicalDeviceVulkan12Properties
p f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_VULKAN_1_2_PROPERTIES)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr DriverId -> DriverId -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr DriverId
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr DriverId)) (DriverId
forall a. Zero a => a
zero)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (FixedArray MAX_DRIVER_NAME_SIZE CChar) -> ByteString -> IO ()
forall (n :: Nat).
KnownNat n =>
Ptr (FixedArray n CChar) -> ByteString -> IO ()
pokeFixedLengthNullTerminatedByteString ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties
-> Int -> Ptr (FixedArray MAX_DRIVER_NAME_SIZE CChar)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr (FixedArray MAX_DRIVER_NAME_SIZE CChar))) (ByteString
forall a. Monoid a => a
mempty)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (FixedArray MAX_DRIVER_NAME_SIZE CChar) -> ByteString -> IO ()
forall (n :: Nat).
KnownNat n =>
Ptr (FixedArray n CChar) -> ByteString -> IO ()
pokeFixedLengthNullTerminatedByteString ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties
-> Int -> Ptr (FixedArray MAX_DRIVER_NAME_SIZE CChar)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 276 :: Ptr (FixedArray MAX_DRIVER_INFO_SIZE CChar))) (ByteString
forall a. Monoid a => a
mempty)
    ((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ConformanceVersion -> ConformanceVersion -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties
-> Int -> Ptr ConformanceVersion
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 532 :: Ptr ConformanceVersion)) (ConformanceVersion
forall a. Zero a => a
zero) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ShaderFloatControlsIndependence
-> ShaderFloatControlsIndependence -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties
-> Int -> Ptr ShaderFloatControlsIndependence
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 536 :: Ptr ShaderFloatControlsIndependence)) (ShaderFloatControlsIndependence
forall a. Zero a => a
zero)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ShaderFloatControlsIndependence
-> ShaderFloatControlsIndependence -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties
-> Int -> Ptr ShaderFloatControlsIndependence
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 540 :: Ptr ShaderFloatControlsIndependence)) (ShaderFloatControlsIndependence
forall a. Zero a => a
zero)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 544 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 548 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 552 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 556 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 560 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 564 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 568 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 572 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 576 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 580 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 584 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 588 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 592 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 596 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 600 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 604 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 608 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 612 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 616 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 620 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 624 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 628 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 632 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 636 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 640 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 644 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 648 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 652 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 656 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 660 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 664 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 668 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 672 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 676 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 680 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 684 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 688 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 692 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ResolveModeFlags -> ResolveModeFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr ResolveModeFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 696 :: Ptr ResolveModeFlags)) (ResolveModeFlags
forall a. Zero a => a
zero)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ResolveModeFlags -> ResolveModeFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr ResolveModeFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 700 :: Ptr ResolveModeFlags)) (ResolveModeFlags
forall a. Zero a => a
zero)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 704 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 708 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 712 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 716 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 720 :: Ptr Word64)) (DeviceSize
forall a. Zero a => a
zero)
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f

instance FromCStruct PhysicalDeviceVulkan12Properties where
  peekCStruct :: Ptr PhysicalDeviceVulkan12Properties
-> IO PhysicalDeviceVulkan12Properties
peekCStruct p :: Ptr PhysicalDeviceVulkan12Properties
p = do
    DriverId
driverID <- Ptr DriverId -> IO DriverId
forall a. Storable a => Ptr a -> IO a
peek @DriverId ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr DriverId
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr DriverId))
    ByteString
driverName <- CString -> IO ByteString
packCString (Ptr (FixedArray MAX_DRIVER_NAME_SIZE CChar) -> CString
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties
-> Int -> Ptr (FixedArray MAX_DRIVER_NAME_SIZE CChar)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr (FixedArray MAX_DRIVER_NAME_SIZE CChar))))
    ByteString
driverInfo <- CString -> IO ByteString
packCString (Ptr (FixedArray MAX_DRIVER_NAME_SIZE CChar) -> CString
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties
-> Int -> Ptr (FixedArray MAX_DRIVER_NAME_SIZE CChar)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 276 :: Ptr (FixedArray MAX_DRIVER_INFO_SIZE CChar))))
    ConformanceVersion
conformanceVersion <- Ptr ConformanceVersion -> IO ConformanceVersion
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @ConformanceVersion ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties
-> Int -> Ptr ConformanceVersion
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 532 :: Ptr ConformanceVersion))
    ShaderFloatControlsIndependence
denormBehaviorIndependence <- Ptr ShaderFloatControlsIndependence
-> IO ShaderFloatControlsIndependence
forall a. Storable a => Ptr a -> IO a
peek @ShaderFloatControlsIndependence ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties
-> Int -> Ptr ShaderFloatControlsIndependence
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 536 :: Ptr ShaderFloatControlsIndependence))
    ShaderFloatControlsIndependence
roundingModeIndependence <- Ptr ShaderFloatControlsIndependence
-> IO ShaderFloatControlsIndependence
forall a. Storable a => Ptr a -> IO a
peek @ShaderFloatControlsIndependence ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties
-> Int -> Ptr ShaderFloatControlsIndependence
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 540 :: Ptr ShaderFloatControlsIndependence))
    Bool32
shaderSignedZeroInfNanPreserveFloat16 <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 544 :: Ptr Bool32))
    Bool32
shaderSignedZeroInfNanPreserveFloat32 <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 548 :: Ptr Bool32))
    Bool32
shaderSignedZeroInfNanPreserveFloat64 <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 552 :: Ptr Bool32))
    Bool32
shaderDenormPreserveFloat16 <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 556 :: Ptr Bool32))
    Bool32
shaderDenormPreserveFloat32 <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 560 :: Ptr Bool32))
    Bool32
shaderDenormPreserveFloat64 <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 564 :: Ptr Bool32))
    Bool32
shaderDenormFlushToZeroFloat16 <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 568 :: Ptr Bool32))
    Bool32
shaderDenormFlushToZeroFloat32 <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 572 :: Ptr Bool32))
    Bool32
shaderDenormFlushToZeroFloat64 <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 576 :: Ptr Bool32))
    Bool32
shaderRoundingModeRTEFloat16 <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 580 :: Ptr Bool32))
    Bool32
shaderRoundingModeRTEFloat32 <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 584 :: Ptr Bool32))
    Bool32
shaderRoundingModeRTEFloat64 <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 588 :: Ptr Bool32))
    Bool32
shaderRoundingModeRTZFloat16 <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 592 :: Ptr Bool32))
    Bool32
shaderRoundingModeRTZFloat32 <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 596 :: Ptr Bool32))
    Bool32
shaderRoundingModeRTZFloat64 <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 600 :: Ptr Bool32))
    Word32
maxUpdateAfterBindDescriptorsInAllPools <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 604 :: Ptr Word32))
    Bool32
shaderUniformBufferArrayNonUniformIndexingNative <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 608 :: Ptr Bool32))
    Bool32
shaderSampledImageArrayNonUniformIndexingNative <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 612 :: Ptr Bool32))
    Bool32
shaderStorageBufferArrayNonUniformIndexingNative <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 616 :: Ptr Bool32))
    Bool32
shaderStorageImageArrayNonUniformIndexingNative <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 620 :: Ptr Bool32))
    Bool32
shaderInputAttachmentArrayNonUniformIndexingNative <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 624 :: Ptr Bool32))
    Bool32
robustBufferAccessUpdateAfterBind <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 628 :: Ptr Bool32))
    Bool32
quadDivergentImplicitLod <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 632 :: Ptr Bool32))
    Word32
maxPerStageDescriptorUpdateAfterBindSamplers <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 636 :: Ptr Word32))
    Word32
maxPerStageDescriptorUpdateAfterBindUniformBuffers <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 640 :: Ptr Word32))
    Word32
maxPerStageDescriptorUpdateAfterBindStorageBuffers <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 644 :: Ptr Word32))
    Word32
maxPerStageDescriptorUpdateAfterBindSampledImages <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 648 :: Ptr Word32))
    Word32
maxPerStageDescriptorUpdateAfterBindStorageImages <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 652 :: Ptr Word32))
    Word32
maxPerStageDescriptorUpdateAfterBindInputAttachments <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 656 :: Ptr Word32))
    Word32
maxPerStageUpdateAfterBindResources <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 660 :: Ptr Word32))
    Word32
maxDescriptorSetUpdateAfterBindSamplers <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 664 :: Ptr Word32))
    Word32
maxDescriptorSetUpdateAfterBindUniformBuffers <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 668 :: Ptr Word32))
    Word32
maxDescriptorSetUpdateAfterBindUniformBuffersDynamic <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 672 :: Ptr Word32))
    Word32
maxDescriptorSetUpdateAfterBindStorageBuffers <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 676 :: Ptr Word32))
    Word32
maxDescriptorSetUpdateAfterBindStorageBuffersDynamic <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 680 :: Ptr Word32))
    Word32
maxDescriptorSetUpdateAfterBindSampledImages <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 684 :: Ptr Word32))
    Word32
maxDescriptorSetUpdateAfterBindStorageImages <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 688 :: Ptr Word32))
    Word32
maxDescriptorSetUpdateAfterBindInputAttachments <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 692 :: Ptr Word32))
    ResolveModeFlags
supportedDepthResolveModes <- Ptr ResolveModeFlags -> IO ResolveModeFlags
forall a. Storable a => Ptr a -> IO a
peek @ResolveModeFlags ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr ResolveModeFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 696 :: Ptr ResolveModeFlags))
    ResolveModeFlags
supportedStencilResolveModes <- Ptr ResolveModeFlags -> IO ResolveModeFlags
forall a. Storable a => Ptr a -> IO a
peek @ResolveModeFlags ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr ResolveModeFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 700 :: Ptr ResolveModeFlags))
    Bool32
independentResolveNone <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 704 :: Ptr Bool32))
    Bool32
independentResolve <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 708 :: Ptr Bool32))
    Bool32
filterMinmaxSingleComponentFormats <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 712 :: Ptr Bool32))
    Bool32
filterMinmaxImageComponentMapping <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 716 :: Ptr Bool32))
    DeviceSize
maxTimelineSemaphoreValueDifference <- Ptr DeviceSize -> IO DeviceSize
forall a. Storable a => Ptr a -> IO a
peek @Word64 ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 720 :: Ptr Word64))
    SampleCountFlags
framebufferIntegerColorSampleCounts <- Ptr SampleCountFlags -> IO SampleCountFlags
forall a. Storable a => Ptr a -> IO a
peek @SampleCountFlags ((Ptr PhysicalDeviceVulkan12Properties
p Ptr PhysicalDeviceVulkan12Properties -> Int -> Ptr SampleCountFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 728 :: Ptr SampleCountFlags))
    PhysicalDeviceVulkan12Properties
-> IO PhysicalDeviceVulkan12Properties
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDeviceVulkan12Properties
 -> IO PhysicalDeviceVulkan12Properties)
-> PhysicalDeviceVulkan12Properties
-> IO PhysicalDeviceVulkan12Properties
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 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
           DriverId
forall a. Zero a => a
zero
           ByteString
forall a. Monoid a => a
mempty
           ByteString
forall a. Monoid a => a
mempty
           ConformanceVersion
forall a. Zero a => a
zero
           ShaderFloatControlsIndependence
forall a. Zero a => a
zero
           ShaderFloatControlsIndependence
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           ResolveModeFlags
forall a. Zero a => a
zero
           ResolveModeFlags
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           DeviceSize
forall a. Zero a => a
zero
           SampleCountFlags
forall a. Zero a => a
zero