{-# language CPP #-}
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))
data PhysicalDeviceRobustness2FeaturesEXT = PhysicalDeviceRobustness2FeaturesEXT
  { 
    PhysicalDeviceRobustness2FeaturesEXT -> Bool
robustBufferAccess2 :: Bool
  , 
    PhysicalDeviceRobustness2FeaturesEXT -> Bool
robustImageAccess2 :: Bool
  , 
    PhysicalDeviceRobustness2FeaturesEXT -> Bool
nullDescriptor :: Bool
  }
  deriving (Typeable, PhysicalDeviceRobustness2FeaturesEXT
-> PhysicalDeviceRobustness2FeaturesEXT -> Bool
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 = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
32 forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceRobustness2FeaturesEXT
p -> 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
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceRobustness2FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_ROBUSTNESS_2_FEATURES_EXT)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceRobustness2FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceRobustness2FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
robustBufferAccess2))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceRobustness2FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
robustImageAccess2))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceRobustness2FeaturesEXT
p 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
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceRobustness2FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_ROBUSTNESS_2_FEATURES_EXT)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceRobustness2FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceRobustness2FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceRobustness2FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceRobustness2FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (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 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 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 forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Bool32))
    forall (f :: * -> *) a. Applicative f => a -> f a
pure 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 = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: Ptr PhysicalDeviceRobustness2FeaturesEXT
-> PhysicalDeviceRobustness2FeaturesEXT -> IO ()
poke Ptr PhysicalDeviceRobustness2FeaturesEXT
ptr PhysicalDeviceRobustness2FeaturesEXT
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceRobustness2FeaturesEXT
ptr PhysicalDeviceRobustness2FeaturesEXT
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PhysicalDeviceRobustness2FeaturesEXT where
  zero :: PhysicalDeviceRobustness2FeaturesEXT
zero = Bool -> Bool -> Bool -> PhysicalDeviceRobustness2FeaturesEXT
PhysicalDeviceRobustness2FeaturesEXT
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero
data PhysicalDeviceRobustness2PropertiesEXT = PhysicalDeviceRobustness2PropertiesEXT
  { 
    
    
    
    
    
    PhysicalDeviceRobustness2PropertiesEXT -> DeviceSize
robustStorageBufferAccessSizeAlignment :: DeviceSize
  , 
    
    
    
    
    
    
    PhysicalDeviceRobustness2PropertiesEXT -> DeviceSize
robustUniformBufferAccessSizeAlignment :: DeviceSize
  }
  deriving (Typeable, PhysicalDeviceRobustness2PropertiesEXT
-> PhysicalDeviceRobustness2PropertiesEXT -> Bool
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 = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
32 forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceRobustness2PropertiesEXT
p -> 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
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceRobustness2PropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_ROBUSTNESS_2_PROPERTIES_EXT)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceRobustness2PropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceRobustness2PropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DeviceSize)) (DeviceSize
robustStorageBufferAccessSizeAlignment)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceRobustness2PropertiesEXT
p 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
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceRobustness2PropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_ROBUSTNESS_2_PROPERTIES_EXT)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceRobustness2PropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceRobustness2PropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DeviceSize)) (forall a. Zero a => a
zero)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceRobustness2PropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr 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 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 forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr DeviceSize))
    forall (f :: * -> *) a. Applicative f => a -> f a
pure 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 = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: Ptr PhysicalDeviceRobustness2PropertiesEXT
-> PhysicalDeviceRobustness2PropertiesEXT -> IO ()
poke Ptr PhysicalDeviceRobustness2PropertiesEXT
ptr PhysicalDeviceRobustness2PropertiesEXT
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceRobustness2PropertiesEXT
ptr PhysicalDeviceRobustness2PropertiesEXT
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PhysicalDeviceRobustness2PropertiesEXT where
  zero :: PhysicalDeviceRobustness2PropertiesEXT
zero = DeviceSize -> DeviceSize -> PhysicalDeviceRobustness2PropertiesEXT
PhysicalDeviceRobustness2PropertiesEXT
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero
type EXT_ROBUSTNESS_2_SPEC_VERSION = 1
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 -> ((# #) -> r) -> ((# #) -> r) -> r
EXT_ROBUSTNESS_2_SPEC_VERSION = 1
type EXT_ROBUSTNESS_2_EXTENSION_NAME = "VK_EXT_robustness2"
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 -> ((# #) -> r) -> ((# #) -> r) -> r
EXT_ROBUSTNESS_2_EXTENSION_NAME = "VK_EXT_robustness2"