{-# language CPP #-}
-- | = Name
--
-- VK_EXT_robustness2 - device extension
--
-- == VK_EXT_robustness2
--
-- [__Name String__]
--     @VK_EXT_robustness2@
--
-- [__Extension Type__]
--     Device extension
--
-- [__Registered Extension Number__]
--     287
--
-- [__Revision__]
--     1
--
-- [__Extension and Version Dependencies__]
--
--     -   Requires support for Vulkan 1.0
--
-- [__Contact__]
--
--     -   Liam Middlebrook
--         <https://github.com/KhronosGroup/Vulkan-Docs/issues/new?body=[VK_EXT_robustness2] @liam-middlebrook%0A*Here describe the issue or question you have about the VK_EXT_robustness2 extension* >
--
-- == Other Extension Metadata
--
-- [__Last Modified Date__]
--     2020-01-29
--
-- [__IP Status__]
--     No known IP claims.
--
-- [__Contributors__]
--
--     -   Liam Middlebrook, NVIDIA
--
--     -   Jeff Bolz, NVIDIA
--
-- == Description
--
-- This extension adds stricter requirements for how out of bounds reads
-- and writes are handled. Most accesses /must/ be tightly bounds-checked,
-- out of bounds writes /must/ be discarded, out of bound reads /must/
-- return zero. Rather than allowing multiple possible (0,0,0,x) vectors,
-- the out of bounds values are treated as zero, and then missing
-- components are inserted based on the format as described in
-- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#textures-conversion-to-rgba Conversion to RGBA>
-- and
-- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#fxvertex-input-extraction vertex input attribute extraction>.
--
-- These additional requirements /may/ be expensive on some
-- implementations, and should only be enabled when truly necessary.
--
-- This extension also adds support for “null descriptors”, where
-- 'Vulkan.Core10.APIConstants.NULL_HANDLE' /can/ be used instead of a
-- valid handle. Accesses to null descriptors have well-defined behavior,
-- and do not rely on robustness.
--
-- == New Structures
--
-- -   Extending
--     'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceFeatures2',
--     'Vulkan.Core10.Device.DeviceCreateInfo':
--
--     -   'PhysicalDeviceRobustness2FeaturesEXT'
--
-- -   Extending
--     'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceProperties2':
--
--     -   'PhysicalDeviceRobustness2PropertiesEXT'
--
-- == New Enum Constants
--
-- -   'EXT_ROBUSTNESS_2_EXTENSION_NAME'
--
-- -   'EXT_ROBUSTNESS_2_SPEC_VERSION'
--
-- -   Extending 'Vulkan.Core10.Enums.StructureType.StructureType':
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PHYSICAL_DEVICE_ROBUSTNESS_2_FEATURES_EXT'
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PHYSICAL_DEVICE_ROBUSTNESS_2_PROPERTIES_EXT'
--
-- == Issues
--
-- 1.  Why do
--     'PhysicalDeviceRobustness2PropertiesEXT'::@robustUniformBufferAccessSizeAlignment@
--     and
--     'PhysicalDeviceRobustness2PropertiesEXT'::@robustStorageBufferAccessSizeAlignment@
--     exist?
--
-- __RESOLVED__: Some implementations cannot efficiently tightly
-- bounds-check all buffer accesses. Rather, the size of the bound range is
-- padded to some power of two multiple, up to 256 bytes for uniform
-- buffers and up to 4 bytes for storage buffers, and that padded size is
-- bounds-checked. This is sufficient to implement D3D-like behavior,
-- because D3D only allows binding whole uniform buffers or ranges that are
-- a multiple of 256 bytes, and D3D raw and structured buffers only support
-- 32-bit accesses.
--
-- == Examples
--
-- None.
--
-- == Version History
--
-- -   Revision 1, 2019-11-01 (Jeff Bolz, Liam Middlebrook)
--
--     -   Initial draft
--
-- == See Also
--
-- 'PhysicalDeviceRobustness2FeaturesEXT',
-- 'PhysicalDeviceRobustness2PropertiesEXT'
--
-- == Document Notes
--
-- For more information, see the
-- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#VK_EXT_robustness2 Vulkan Specification>
--
-- This page is a generated document. Fixes and changes should be made to
-- the generator scripts, not directly.
module Vulkan.Extensions.VK_EXT_robustness2  ( PhysicalDeviceRobustness2FeaturesEXT(..)
                                             , PhysicalDeviceRobustness2PropertiesEXT(..)
                                             , EXT_ROBUSTNESS_2_SPEC_VERSION
                                             , pattern EXT_ROBUSTNESS_2_SPEC_VERSION
                                             , EXT_ROBUSTNESS_2_EXTENSION_NAME
                                             , pattern EXT_ROBUSTNESS_2_EXTENSION_NAME
                                             ) where

import Foreign.Marshal.Alloc (allocaBytes)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Zero (Zero(..))
import Data.String (IsString)
import Data.Typeable (Typeable)
import Foreign.Storable (Storable)
import Foreign.Storable (Storable(peek))
import Foreign.Storable (Storable(poke))
import qualified Foreign.Storable (Storable(..))
import GHC.Generics (Generic)
import Foreign.Ptr (Ptr)
import Data.Kind (Type)
import Vulkan.Core10.FundamentalTypes (bool32ToBool)
import Vulkan.Core10.FundamentalTypes (boolToBool32)
import Vulkan.Core10.FundamentalTypes (Bool32)
import Vulkan.Core10.FundamentalTypes (DeviceSize)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_ROBUSTNESS_2_FEATURES_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_ROBUSTNESS_2_PROPERTIES_EXT))
-- | VkPhysicalDeviceRobustness2FeaturesEXT - Structure describing the
-- out-of-bounds behavior for an implementation
--
-- = Members
--
-- This structure describes the following features:
--
-- = Description
--
-- -   @sType@ is the type of this structure.
--
-- -   @pNext@ is @NULL@ or a pointer to a structure extending this
--     structure.
--
-- -   #features-robustBufferAccess2# @robustBufferAccess2@ indicates
--     whether buffer accesses are tightly bounds-checked against the range
--     of the descriptor. Uniform buffers /must/ be bounds-checked to the
--     range of the descriptor, where the range is rounded up to a multiple
--     of
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#limits-robustUniformBufferAccessSizeAlignment robustUniformBufferAccessSizeAlignment>.
--     Storage buffers /must/ be bounds-checked to the range of the
--     descriptor, where the range is rounded up to a multiple of
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#limits-robustStorageBufferAccessSizeAlignment robustStorageBufferAccessSizeAlignment>.
--     Out of bounds buffer loads will return zero values, and
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#textures image load, sample, and atomic operations>
--     from texel buffers will have (0,0,1) values
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#textures-conversion-to-rgba inserted for missing G, B, or A components>
--     based on the format.
--
-- -   #features-robustImageAccess2# @robustImageAccess2@ indicates whether
--     image accesses are tightly bounds-checked against the dimensions of
--     the image view. Out of bounds
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#textures image load, sample, and atomic operations>
--     from images will return zero values, with (0,0,1) values
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#textures-conversion-to-rgba inserted for missing G, B, or A components>
--     based on the format.
--
-- -   #features-nullDescriptor# @nullDescriptor@ indicates whether
--     descriptors /can/ be written with a
--     'Vulkan.Core10.APIConstants.NULL_HANDLE' resource or view, which are
--     considered valid to access and act as if the descriptor were bound
--     to nothing.
--
-- If the 'PhysicalDeviceRobustness2FeaturesEXT' structure is included in
-- the @pNext@ chain of the
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceFeatures2'
-- structure passed to
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.getPhysicalDeviceFeatures2',
-- it is filled in to indicate whether each corresponding feature is
-- supported. 'PhysicalDeviceRobustness2FeaturesEXT' /can/ also be used in
-- the @pNext@ chain of 'Vulkan.Core10.Device.DeviceCreateInfo' to
-- selectively enable these features.
--
-- == Valid Usage
--
-- -   #VUID-VkPhysicalDeviceRobustness2FeaturesEXT-robustBufferAccess2-04000#
--     If @robustBufferAccess2@ is enabled then
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-robustBufferAccess robustBufferAccess>
--     /must/ also be enabled
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-VkPhysicalDeviceRobustness2FeaturesEXT-sType-sType# @sType@
--     /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PHYSICAL_DEVICE_ROBUSTNESS_2_FEATURES_EXT'
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_robustness2 VK_EXT_robustness2>,
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDeviceRobustness2FeaturesEXT = PhysicalDeviceRobustness2FeaturesEXT
  { -- No documentation found for Nested "VkPhysicalDeviceRobustness2FeaturesEXT" "robustBufferAccess2"
    PhysicalDeviceRobustness2FeaturesEXT -> Bool
robustBufferAccess2 :: Bool
  , -- No documentation found for Nested "VkPhysicalDeviceRobustness2FeaturesEXT" "robustImageAccess2"
    PhysicalDeviceRobustness2FeaturesEXT -> Bool
robustImageAccess2 :: Bool
  , -- No documentation found for Nested "VkPhysicalDeviceRobustness2FeaturesEXT" "nullDescriptor"
    PhysicalDeviceRobustness2FeaturesEXT -> Bool
nullDescriptor :: Bool
  }
  deriving (Typeable, PhysicalDeviceRobustness2FeaturesEXT
-> PhysicalDeviceRobustness2FeaturesEXT -> Bool
(PhysicalDeviceRobustness2FeaturesEXT
 -> PhysicalDeviceRobustness2FeaturesEXT -> Bool)
-> (PhysicalDeviceRobustness2FeaturesEXT
    -> PhysicalDeviceRobustness2FeaturesEXT -> Bool)
-> Eq PhysicalDeviceRobustness2FeaturesEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceRobustness2FeaturesEXT
-> PhysicalDeviceRobustness2FeaturesEXT -> Bool
$c/= :: PhysicalDeviceRobustness2FeaturesEXT
-> PhysicalDeviceRobustness2FeaturesEXT -> Bool
== :: PhysicalDeviceRobustness2FeaturesEXT
-> PhysicalDeviceRobustness2FeaturesEXT -> Bool
$c== :: PhysicalDeviceRobustness2FeaturesEXT
-> PhysicalDeviceRobustness2FeaturesEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceRobustness2FeaturesEXT)
#endif
deriving instance Show PhysicalDeviceRobustness2FeaturesEXT

instance ToCStruct PhysicalDeviceRobustness2FeaturesEXT where
  withCStruct :: forall b.
PhysicalDeviceRobustness2FeaturesEXT
-> (Ptr PhysicalDeviceRobustness2FeaturesEXT -> IO b) -> IO b
withCStruct PhysicalDeviceRobustness2FeaturesEXT
x Ptr PhysicalDeviceRobustness2FeaturesEXT -> IO b
f = Int -> (Ptr PhysicalDeviceRobustness2FeaturesEXT -> IO b) -> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
32 ((Ptr PhysicalDeviceRobustness2FeaturesEXT -> IO b) -> IO b)
-> (Ptr PhysicalDeviceRobustness2FeaturesEXT -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceRobustness2FeaturesEXT
p -> Ptr PhysicalDeviceRobustness2FeaturesEXT
-> PhysicalDeviceRobustness2FeaturesEXT -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceRobustness2FeaturesEXT
p PhysicalDeviceRobustness2FeaturesEXT
x (Ptr PhysicalDeviceRobustness2FeaturesEXT -> IO b
f Ptr PhysicalDeviceRobustness2FeaturesEXT
p)
  pokeCStruct :: forall b.
Ptr PhysicalDeviceRobustness2FeaturesEXT
-> PhysicalDeviceRobustness2FeaturesEXT -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceRobustness2FeaturesEXT
p PhysicalDeviceRobustness2FeaturesEXT{Bool
nullDescriptor :: Bool
robustImageAccess2 :: Bool
robustBufferAccess2 :: Bool
$sel:nullDescriptor:PhysicalDeviceRobustness2FeaturesEXT :: PhysicalDeviceRobustness2FeaturesEXT -> Bool
$sel:robustImageAccess2:PhysicalDeviceRobustness2FeaturesEXT :: PhysicalDeviceRobustness2FeaturesEXT -> Bool
$sel:robustBufferAccess2:PhysicalDeviceRobustness2FeaturesEXT :: PhysicalDeviceRobustness2FeaturesEXT -> Bool
..} IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceRobustness2FeaturesEXT
p Ptr PhysicalDeviceRobustness2FeaturesEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_ROBUSTNESS_2_FEATURES_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceRobustness2FeaturesEXT
p Ptr PhysicalDeviceRobustness2FeaturesEXT -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceRobustness2FeaturesEXT
p Ptr PhysicalDeviceRobustness2FeaturesEXT -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
robustBufferAccess2))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceRobustness2FeaturesEXT
p Ptr PhysicalDeviceRobustness2FeaturesEXT -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
robustImageAccess2))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceRobustness2FeaturesEXT
p Ptr PhysicalDeviceRobustness2FeaturesEXT -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
nullDescriptor))
    IO b
f
  cStructSize :: Int
cStructSize = Int
32
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b. Ptr PhysicalDeviceRobustness2FeaturesEXT -> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceRobustness2FeaturesEXT
p IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceRobustness2FeaturesEXT
p Ptr PhysicalDeviceRobustness2FeaturesEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_ROBUSTNESS_2_FEATURES_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceRobustness2FeaturesEXT
p Ptr PhysicalDeviceRobustness2FeaturesEXT -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceRobustness2FeaturesEXT
p Ptr PhysicalDeviceRobustness2FeaturesEXT -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
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 PhysicalDeviceRobustness2FeaturesEXT
p Ptr PhysicalDeviceRobustness2FeaturesEXT -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
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 PhysicalDeviceRobustness2FeaturesEXT
p Ptr PhysicalDeviceRobustness2FeaturesEXT -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    IO b
f

instance FromCStruct PhysicalDeviceRobustness2FeaturesEXT where
  peekCStruct :: Ptr PhysicalDeviceRobustness2FeaturesEXT
-> IO PhysicalDeviceRobustness2FeaturesEXT
peekCStruct Ptr PhysicalDeviceRobustness2FeaturesEXT
p = do
    Bool32
robustBufferAccess2 <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceRobustness2FeaturesEXT
p Ptr PhysicalDeviceRobustness2FeaturesEXT -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32))
    Bool32
robustImageAccess2 <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceRobustness2FeaturesEXT
p Ptr PhysicalDeviceRobustness2FeaturesEXT -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32))
    Bool32
nullDescriptor <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceRobustness2FeaturesEXT
p Ptr PhysicalDeviceRobustness2FeaturesEXT -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Bool32))
    PhysicalDeviceRobustness2FeaturesEXT
-> IO PhysicalDeviceRobustness2FeaturesEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDeviceRobustness2FeaturesEXT
 -> IO PhysicalDeviceRobustness2FeaturesEXT)
-> PhysicalDeviceRobustness2FeaturesEXT
-> IO PhysicalDeviceRobustness2FeaturesEXT
forall a b. (a -> b) -> a -> b
$ Bool -> Bool -> Bool -> PhysicalDeviceRobustness2FeaturesEXT
PhysicalDeviceRobustness2FeaturesEXT
             (Bool32 -> Bool
bool32ToBool Bool32
robustBufferAccess2)
             (Bool32 -> Bool
bool32ToBool Bool32
robustImageAccess2)
             (Bool32 -> Bool
bool32ToBool Bool32
nullDescriptor)

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

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


-- | VkPhysicalDeviceRobustness2PropertiesEXT - Structure describing robust
-- buffer access properties supported by an implementation
--
-- = Description
--
-- If the 'PhysicalDeviceRobustness2PropertiesEXT' structure is included in
-- the @pNext@ chain of the
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceProperties2'
-- structure passed to
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.getPhysicalDeviceProperties2',
-- it is filled in with each corresponding implementation-dependent
-- property.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_robustness2 VK_EXT_robustness2>,
-- 'Vulkan.Core10.FundamentalTypes.DeviceSize',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDeviceRobustness2PropertiesEXT = PhysicalDeviceRobustness2PropertiesEXT
  { -- | #limits-robustStorageBufferAccessSizeAlignment#
    -- @robustStorageBufferAccessSizeAlignment@ is the number of bytes that the
    -- range of a storage buffer descriptor is rounded up to when used for
    -- bounds-checking when the
    -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-robustBufferAccess2 robustBufferAccess2>
    -- feature is enabled. This value /must/ be either 1 or 4.
    PhysicalDeviceRobustness2PropertiesEXT -> DeviceSize
robustStorageBufferAccessSizeAlignment :: DeviceSize
  , -- | #limits-robustUniformBufferAccessSizeAlignment#
    -- @robustUniformBufferAccessSizeAlignment@ is the number of bytes that the
    -- range of a uniform buffer descriptor is rounded up to when used for
    -- bounds-checking when the
    -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-robustBufferAccess2 robustBufferAccess2>
    -- feature is enabled. This value /must/ be a power of two in the range [1,
    -- 256].
    PhysicalDeviceRobustness2PropertiesEXT -> DeviceSize
robustUniformBufferAccessSizeAlignment :: DeviceSize
  }
  deriving (Typeable, PhysicalDeviceRobustness2PropertiesEXT
-> PhysicalDeviceRobustness2PropertiesEXT -> Bool
(PhysicalDeviceRobustness2PropertiesEXT
 -> PhysicalDeviceRobustness2PropertiesEXT -> Bool)
-> (PhysicalDeviceRobustness2PropertiesEXT
    -> PhysicalDeviceRobustness2PropertiesEXT -> Bool)
-> Eq PhysicalDeviceRobustness2PropertiesEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceRobustness2PropertiesEXT
-> PhysicalDeviceRobustness2PropertiesEXT -> Bool
$c/= :: PhysicalDeviceRobustness2PropertiesEXT
-> PhysicalDeviceRobustness2PropertiesEXT -> Bool
== :: PhysicalDeviceRobustness2PropertiesEXT
-> PhysicalDeviceRobustness2PropertiesEXT -> Bool
$c== :: PhysicalDeviceRobustness2PropertiesEXT
-> PhysicalDeviceRobustness2PropertiesEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceRobustness2PropertiesEXT)
#endif
deriving instance Show PhysicalDeviceRobustness2PropertiesEXT

instance ToCStruct PhysicalDeviceRobustness2PropertiesEXT where
  withCStruct :: forall b.
PhysicalDeviceRobustness2PropertiesEXT
-> (Ptr PhysicalDeviceRobustness2PropertiesEXT -> IO b) -> IO b
withCStruct PhysicalDeviceRobustness2PropertiesEXT
x Ptr PhysicalDeviceRobustness2PropertiesEXT -> IO b
f = Int -> (Ptr PhysicalDeviceRobustness2PropertiesEXT -> IO b) -> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
32 ((Ptr PhysicalDeviceRobustness2PropertiesEXT -> IO b) -> IO b)
-> (Ptr PhysicalDeviceRobustness2PropertiesEXT -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceRobustness2PropertiesEXT
p -> Ptr PhysicalDeviceRobustness2PropertiesEXT
-> PhysicalDeviceRobustness2PropertiesEXT -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceRobustness2PropertiesEXT
p PhysicalDeviceRobustness2PropertiesEXT
x (Ptr PhysicalDeviceRobustness2PropertiesEXT -> IO b
f Ptr PhysicalDeviceRobustness2PropertiesEXT
p)
  pokeCStruct :: forall b.
Ptr PhysicalDeviceRobustness2PropertiesEXT
-> PhysicalDeviceRobustness2PropertiesEXT -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceRobustness2PropertiesEXT
p PhysicalDeviceRobustness2PropertiesEXT{DeviceSize
robustUniformBufferAccessSizeAlignment :: DeviceSize
robustStorageBufferAccessSizeAlignment :: DeviceSize
$sel:robustUniformBufferAccessSizeAlignment:PhysicalDeviceRobustness2PropertiesEXT :: PhysicalDeviceRobustness2PropertiesEXT -> DeviceSize
$sel:robustStorageBufferAccessSizeAlignment:PhysicalDeviceRobustness2PropertiesEXT :: PhysicalDeviceRobustness2PropertiesEXT -> DeviceSize
..} IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceRobustness2PropertiesEXT
p Ptr PhysicalDeviceRobustness2PropertiesEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_ROBUSTNESS_2_PROPERTIES_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceRobustness2PropertiesEXT
p Ptr PhysicalDeviceRobustness2PropertiesEXT -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceRobustness2PropertiesEXT
p Ptr PhysicalDeviceRobustness2PropertiesEXT -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DeviceSize)) (DeviceSize
robustStorageBufferAccessSizeAlignment)
    Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceRobustness2PropertiesEXT
p Ptr PhysicalDeviceRobustness2PropertiesEXT -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr DeviceSize)) (DeviceSize
robustUniformBufferAccessSizeAlignment)
    IO b
f
  cStructSize :: Int
cStructSize = Int
32
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b.
Ptr PhysicalDeviceRobustness2PropertiesEXT -> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceRobustness2PropertiesEXT
p IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceRobustness2PropertiesEXT
p Ptr PhysicalDeviceRobustness2PropertiesEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_ROBUSTNESS_2_PROPERTIES_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceRobustness2PropertiesEXT
p Ptr PhysicalDeviceRobustness2PropertiesEXT -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceRobustness2PropertiesEXT
p Ptr PhysicalDeviceRobustness2PropertiesEXT -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DeviceSize)) (DeviceSize
forall a. Zero a => a
zero)
    Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceRobustness2PropertiesEXT
p Ptr PhysicalDeviceRobustness2PropertiesEXT -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr DeviceSize)) (DeviceSize
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct PhysicalDeviceRobustness2PropertiesEXT where
  peekCStruct :: Ptr PhysicalDeviceRobustness2PropertiesEXT
-> IO PhysicalDeviceRobustness2PropertiesEXT
peekCStruct Ptr PhysicalDeviceRobustness2PropertiesEXT
p = do
    DeviceSize
robustStorageBufferAccessSizeAlignment <- forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr PhysicalDeviceRobustness2PropertiesEXT
p Ptr PhysicalDeviceRobustness2PropertiesEXT -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DeviceSize))
    DeviceSize
robustUniformBufferAccessSizeAlignment <- forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr PhysicalDeviceRobustness2PropertiesEXT
p Ptr PhysicalDeviceRobustness2PropertiesEXT -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr DeviceSize))
    PhysicalDeviceRobustness2PropertiesEXT
-> IO PhysicalDeviceRobustness2PropertiesEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDeviceRobustness2PropertiesEXT
 -> IO PhysicalDeviceRobustness2PropertiesEXT)
-> PhysicalDeviceRobustness2PropertiesEXT
-> IO PhysicalDeviceRobustness2PropertiesEXT
forall a b. (a -> b) -> a -> b
$ DeviceSize -> DeviceSize -> PhysicalDeviceRobustness2PropertiesEXT
PhysicalDeviceRobustness2PropertiesEXT
             DeviceSize
robustStorageBufferAccessSizeAlignment
             DeviceSize
robustUniformBufferAccessSizeAlignment

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

instance Zero PhysicalDeviceRobustness2PropertiesEXT where
  zero :: PhysicalDeviceRobustness2PropertiesEXT
zero = DeviceSize -> DeviceSize -> PhysicalDeviceRobustness2PropertiesEXT
PhysicalDeviceRobustness2PropertiesEXT
           DeviceSize
forall a. Zero a => a
zero
           DeviceSize
forall a. Zero a => a
zero


type EXT_ROBUSTNESS_2_SPEC_VERSION = 1

-- No documentation found for TopLevel "VK_EXT_ROBUSTNESS_2_SPEC_VERSION"
pattern EXT_ROBUSTNESS_2_SPEC_VERSION :: forall a . Integral a => a
pattern $bEXT_ROBUSTNESS_2_SPEC_VERSION :: forall a. Integral a => a
$mEXT_ROBUSTNESS_2_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> (Void# -> r) -> (Void# -> r) -> r
EXT_ROBUSTNESS_2_SPEC_VERSION = 1


type EXT_ROBUSTNESS_2_EXTENSION_NAME = "VK_EXT_robustness2"

-- No documentation found for TopLevel "VK_EXT_ROBUSTNESS_2_EXTENSION_NAME"
pattern EXT_ROBUSTNESS_2_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bEXT_ROBUSTNESS_2_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
$mEXT_ROBUSTNESS_2_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> (Void# -> r) -> (Void# -> r) -> r
EXT_ROBUSTNESS_2_EXTENSION_NAME = "VK_EXT_robustness2"