{-# language CPP #-}
module Vulkan.Extensions.VK_EXT_texel_buffer_alignment  ( PhysicalDeviceTexelBufferAlignmentFeaturesEXT(..)
                                                        , PhysicalDeviceTexelBufferAlignmentPropertiesEXT(..)
                                                        , EXT_TEXEL_BUFFER_ALIGNMENT_SPEC_VERSION
                                                        , pattern EXT_TEXEL_BUFFER_ALIGNMENT_SPEC_VERSION
                                                        , EXT_TEXEL_BUFFER_ALIGNMENT_EXTENSION_NAME
                                                        , pattern EXT_TEXEL_BUFFER_ALIGNMENT_EXTENSION_NAME
                                                        ) where

import Foreign.Marshal.Alloc (allocaBytesAligned)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
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.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Zero (Zero(..))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_TEXEL_BUFFER_ALIGNMENT_FEATURES_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_TEXEL_BUFFER_ALIGNMENT_PROPERTIES_EXT))
-- | VkPhysicalDeviceTexelBufferAlignmentFeaturesEXT - Structure describing
-- the texel buffer alignment features that can be supported by an
-- implementation
--
-- = Members
--
-- The members of the 'PhysicalDeviceTexelBufferAlignmentFeaturesEXT'
-- structure describe the following features:
--
-- = Description
--
-- If the 'PhysicalDeviceTexelBufferAlignmentFeaturesEXT' 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 the feature is supported.
-- 'PhysicalDeviceTexelBufferAlignmentFeaturesEXT' /can/ also be included
-- in the @pNext@ chain of 'Vulkan.Core10.Device.DeviceCreateInfo' to
-- enable the feature.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDeviceTexelBufferAlignmentFeaturesEXT = PhysicalDeviceTexelBufferAlignmentFeaturesEXT
  { -- | @texelBufferAlignment@ indicates whether the implementation uses more
    -- specific alignment requirements advertised in
    -- 'PhysicalDeviceTexelBufferAlignmentPropertiesEXT' rather than
    -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@minTexelBufferOffsetAlignment@.
    PhysicalDeviceTexelBufferAlignmentFeaturesEXT -> Bool
texelBufferAlignment :: Bool }
  deriving (Typeable, PhysicalDeviceTexelBufferAlignmentFeaturesEXT
-> PhysicalDeviceTexelBufferAlignmentFeaturesEXT -> Bool
(PhysicalDeviceTexelBufferAlignmentFeaturesEXT
 -> PhysicalDeviceTexelBufferAlignmentFeaturesEXT -> Bool)
-> (PhysicalDeviceTexelBufferAlignmentFeaturesEXT
    -> PhysicalDeviceTexelBufferAlignmentFeaturesEXT -> Bool)
-> Eq PhysicalDeviceTexelBufferAlignmentFeaturesEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceTexelBufferAlignmentFeaturesEXT
-> PhysicalDeviceTexelBufferAlignmentFeaturesEXT -> Bool
$c/= :: PhysicalDeviceTexelBufferAlignmentFeaturesEXT
-> PhysicalDeviceTexelBufferAlignmentFeaturesEXT -> Bool
== :: PhysicalDeviceTexelBufferAlignmentFeaturesEXT
-> PhysicalDeviceTexelBufferAlignmentFeaturesEXT -> Bool
$c== :: PhysicalDeviceTexelBufferAlignmentFeaturesEXT
-> PhysicalDeviceTexelBufferAlignmentFeaturesEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceTexelBufferAlignmentFeaturesEXT)
#endif
deriving instance Show PhysicalDeviceTexelBufferAlignmentFeaturesEXT

instance ToCStruct PhysicalDeviceTexelBufferAlignmentFeaturesEXT where
  withCStruct :: PhysicalDeviceTexelBufferAlignmentFeaturesEXT
-> (Ptr PhysicalDeviceTexelBufferAlignmentFeaturesEXT -> IO b)
-> IO b
withCStruct x :: PhysicalDeviceTexelBufferAlignmentFeaturesEXT
x f :: Ptr PhysicalDeviceTexelBufferAlignmentFeaturesEXT -> IO b
f = Int
-> Int
-> (Ptr PhysicalDeviceTexelBufferAlignmentFeaturesEXT -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 8 ((Ptr PhysicalDeviceTexelBufferAlignmentFeaturesEXT -> IO b)
 -> IO b)
-> (Ptr PhysicalDeviceTexelBufferAlignmentFeaturesEXT -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr PhysicalDeviceTexelBufferAlignmentFeaturesEXT
p -> Ptr PhysicalDeviceTexelBufferAlignmentFeaturesEXT
-> PhysicalDeviceTexelBufferAlignmentFeaturesEXT -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceTexelBufferAlignmentFeaturesEXT
p PhysicalDeviceTexelBufferAlignmentFeaturesEXT
x (Ptr PhysicalDeviceTexelBufferAlignmentFeaturesEXT -> IO b
f Ptr PhysicalDeviceTexelBufferAlignmentFeaturesEXT
p)
  pokeCStruct :: Ptr PhysicalDeviceTexelBufferAlignmentFeaturesEXT
-> PhysicalDeviceTexelBufferAlignmentFeaturesEXT -> IO b -> IO b
pokeCStruct p :: Ptr PhysicalDeviceTexelBufferAlignmentFeaturesEXT
p PhysicalDeviceTexelBufferAlignmentFeaturesEXT{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceTexelBufferAlignmentFeaturesEXT
p Ptr PhysicalDeviceTexelBufferAlignmentFeaturesEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_TEXEL_BUFFER_ALIGNMENT_FEATURES_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceTexelBufferAlignmentFeaturesEXT
p Ptr PhysicalDeviceTexelBufferAlignmentFeaturesEXT
-> 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 PhysicalDeviceTexelBufferAlignmentFeaturesEXT
p Ptr PhysicalDeviceTexelBufferAlignmentFeaturesEXT
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
texelBufferAlignment))
    IO b
f
  cStructSize :: Int
cStructSize = 24
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr PhysicalDeviceTexelBufferAlignmentFeaturesEXT -> IO b -> IO b
pokeZeroCStruct p :: Ptr PhysicalDeviceTexelBufferAlignmentFeaturesEXT
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceTexelBufferAlignmentFeaturesEXT
p Ptr PhysicalDeviceTexelBufferAlignmentFeaturesEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_TEXEL_BUFFER_ALIGNMENT_FEATURES_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceTexelBufferAlignmentFeaturesEXT
p Ptr PhysicalDeviceTexelBufferAlignmentFeaturesEXT
-> 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 PhysicalDeviceTexelBufferAlignmentFeaturesEXT
p Ptr PhysicalDeviceTexelBufferAlignmentFeaturesEXT
-> 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))
    IO b
f

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

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

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


-- | VkPhysicalDeviceTexelBufferAlignmentPropertiesEXT - Structure describing
-- the texel buffer alignment requirements supported by an implementation
--
-- = Members
--
-- The members of the 'PhysicalDeviceTexelBufferAlignmentPropertiesEXT'
-- structure describe the following implementation-dependent limits:
--
-- = Description
--
-- If the 'PhysicalDeviceTexelBufferAlignmentPropertiesEXT' structure is
-- included in the @pNext@ chain of
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceProperties2',
-- it is filled with the implementation-dependent limits.
--
-- If the single texel alignment property is
-- 'Vulkan.Core10.FundamentalTypes.FALSE', then the buffer view’s offset
-- /must/ be aligned to the corresponding byte alignment value. If the
-- single texel alignment property is
-- 'Vulkan.Core10.FundamentalTypes.TRUE', then the buffer view’s offset
-- /must/ be aligned to the lesser of the corresponding byte alignment
-- value or the size of a single texel, based on
-- 'Vulkan.Core10.BufferView.BufferViewCreateInfo'::@format@. If the size
-- of a single texel is a multiple of three bytes, then the size of a
-- single component of the format is used instead.
--
-- These limits /must/ not advertise a larger alignment than the
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-required required>
-- maximum minimum value of
-- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@minTexelBufferOffsetAlignment@,
-- for any format that supports use as a texel buffer.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.FundamentalTypes.DeviceSize',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDeviceTexelBufferAlignmentPropertiesEXT = PhysicalDeviceTexelBufferAlignmentPropertiesEXT
  { -- | @storageTexelBufferOffsetAlignmentBytes@ is a byte alignment that is
    -- sufficient for a storage texel buffer of any format.
    PhysicalDeviceTexelBufferAlignmentPropertiesEXT -> DeviceSize
storageTexelBufferOffsetAlignmentBytes :: DeviceSize
  , -- | @storageTexelBufferOffsetSingleTexelAlignment@ indicates whether single
    -- texel alignment is sufficient for a storage texel buffer of any format.
    PhysicalDeviceTexelBufferAlignmentPropertiesEXT -> Bool
storageTexelBufferOffsetSingleTexelAlignment :: Bool
  , -- | @uniformTexelBufferOffsetAlignmentBytes@ is a byte alignment that is
    -- sufficient for a uniform texel buffer of any format.
    PhysicalDeviceTexelBufferAlignmentPropertiesEXT -> DeviceSize
uniformTexelBufferOffsetAlignmentBytes :: DeviceSize
  , -- | @uniformTexelBufferOffsetSingleTexelAlignment@ indicates whether single
    -- texel alignment is sufficient for a uniform texel buffer of any format.
    PhysicalDeviceTexelBufferAlignmentPropertiesEXT -> Bool
uniformTexelBufferOffsetSingleTexelAlignment :: Bool
  }
  deriving (Typeable, PhysicalDeviceTexelBufferAlignmentPropertiesEXT
-> PhysicalDeviceTexelBufferAlignmentPropertiesEXT -> Bool
(PhysicalDeviceTexelBufferAlignmentPropertiesEXT
 -> PhysicalDeviceTexelBufferAlignmentPropertiesEXT -> Bool)
-> (PhysicalDeviceTexelBufferAlignmentPropertiesEXT
    -> PhysicalDeviceTexelBufferAlignmentPropertiesEXT -> Bool)
-> Eq PhysicalDeviceTexelBufferAlignmentPropertiesEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceTexelBufferAlignmentPropertiesEXT
-> PhysicalDeviceTexelBufferAlignmentPropertiesEXT -> Bool
$c/= :: PhysicalDeviceTexelBufferAlignmentPropertiesEXT
-> PhysicalDeviceTexelBufferAlignmentPropertiesEXT -> Bool
== :: PhysicalDeviceTexelBufferAlignmentPropertiesEXT
-> PhysicalDeviceTexelBufferAlignmentPropertiesEXT -> Bool
$c== :: PhysicalDeviceTexelBufferAlignmentPropertiesEXT
-> PhysicalDeviceTexelBufferAlignmentPropertiesEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceTexelBufferAlignmentPropertiesEXT)
#endif
deriving instance Show PhysicalDeviceTexelBufferAlignmentPropertiesEXT

instance ToCStruct PhysicalDeviceTexelBufferAlignmentPropertiesEXT where
  withCStruct :: PhysicalDeviceTexelBufferAlignmentPropertiesEXT
-> (Ptr PhysicalDeviceTexelBufferAlignmentPropertiesEXT -> IO b)
-> IO b
withCStruct x :: PhysicalDeviceTexelBufferAlignmentPropertiesEXT
x f :: Ptr PhysicalDeviceTexelBufferAlignmentPropertiesEXT -> IO b
f = Int
-> Int
-> (Ptr PhysicalDeviceTexelBufferAlignmentPropertiesEXT -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 48 8 ((Ptr PhysicalDeviceTexelBufferAlignmentPropertiesEXT -> IO b)
 -> IO b)
-> (Ptr PhysicalDeviceTexelBufferAlignmentPropertiesEXT -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr PhysicalDeviceTexelBufferAlignmentPropertiesEXT
p -> Ptr PhysicalDeviceTexelBufferAlignmentPropertiesEXT
-> PhysicalDeviceTexelBufferAlignmentPropertiesEXT -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceTexelBufferAlignmentPropertiesEXT
p PhysicalDeviceTexelBufferAlignmentPropertiesEXT
x (Ptr PhysicalDeviceTexelBufferAlignmentPropertiesEXT -> IO b
f Ptr PhysicalDeviceTexelBufferAlignmentPropertiesEXT
p)
  pokeCStruct :: Ptr PhysicalDeviceTexelBufferAlignmentPropertiesEXT
-> PhysicalDeviceTexelBufferAlignmentPropertiesEXT -> IO b -> IO b
pokeCStruct p :: Ptr PhysicalDeviceTexelBufferAlignmentPropertiesEXT
p PhysicalDeviceTexelBufferAlignmentPropertiesEXT{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceTexelBufferAlignmentPropertiesEXT
p Ptr PhysicalDeviceTexelBufferAlignmentPropertiesEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_TEXEL_BUFFER_ALIGNMENT_PROPERTIES_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceTexelBufferAlignmentPropertiesEXT
p Ptr PhysicalDeviceTexelBufferAlignmentPropertiesEXT
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceTexelBufferAlignmentPropertiesEXT
p Ptr PhysicalDeviceTexelBufferAlignmentPropertiesEXT
-> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr DeviceSize)) (DeviceSize
storageTexelBufferOffsetAlignmentBytes)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceTexelBufferAlignmentPropertiesEXT
p Ptr PhysicalDeviceTexelBufferAlignmentPropertiesEXT
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
storageTexelBufferOffsetSingleTexelAlignment))
    Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceTexelBufferAlignmentPropertiesEXT
p Ptr PhysicalDeviceTexelBufferAlignmentPropertiesEXT
-> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr DeviceSize)) (DeviceSize
uniformTexelBufferOffsetAlignmentBytes)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceTexelBufferAlignmentPropertiesEXT
p Ptr PhysicalDeviceTexelBufferAlignmentPropertiesEXT
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
uniformTexelBufferOffsetSingleTexelAlignment))
    IO b
f
  cStructSize :: Int
cStructSize = 48
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr PhysicalDeviceTexelBufferAlignmentPropertiesEXT -> IO b -> IO b
pokeZeroCStruct p :: Ptr PhysicalDeviceTexelBufferAlignmentPropertiesEXT
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceTexelBufferAlignmentPropertiesEXT
p Ptr PhysicalDeviceTexelBufferAlignmentPropertiesEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_TEXEL_BUFFER_ALIGNMENT_PROPERTIES_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceTexelBufferAlignmentPropertiesEXT
p Ptr PhysicalDeviceTexelBufferAlignmentPropertiesEXT
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceTexelBufferAlignmentPropertiesEXT
p Ptr PhysicalDeviceTexelBufferAlignmentPropertiesEXT
-> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr DeviceSize)) (DeviceSize
forall a. Zero a => a
zero)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceTexelBufferAlignmentPropertiesEXT
p Ptr PhysicalDeviceTexelBufferAlignmentPropertiesEXT
-> 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 DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceTexelBufferAlignmentPropertiesEXT
p Ptr PhysicalDeviceTexelBufferAlignmentPropertiesEXT
-> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr DeviceSize)) (DeviceSize
forall a. Zero a => a
zero)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceTexelBufferAlignmentPropertiesEXT
p Ptr PhysicalDeviceTexelBufferAlignmentPropertiesEXT
-> 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))
    IO b
f

instance FromCStruct PhysicalDeviceTexelBufferAlignmentPropertiesEXT where
  peekCStruct :: Ptr PhysicalDeviceTexelBufferAlignmentPropertiesEXT
-> IO PhysicalDeviceTexelBufferAlignmentPropertiesEXT
peekCStruct p :: Ptr PhysicalDeviceTexelBufferAlignmentPropertiesEXT
p = do
    DeviceSize
storageTexelBufferOffsetAlignmentBytes <- Ptr DeviceSize -> IO DeviceSize
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr PhysicalDeviceTexelBufferAlignmentPropertiesEXT
p Ptr PhysicalDeviceTexelBufferAlignmentPropertiesEXT
-> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr DeviceSize))
    Bool32
storageTexelBufferOffsetSingleTexelAlignment <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceTexelBufferAlignmentPropertiesEXT
p Ptr PhysicalDeviceTexelBufferAlignmentPropertiesEXT
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Bool32))
    DeviceSize
uniformTexelBufferOffsetAlignmentBytes <- Ptr DeviceSize -> IO DeviceSize
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr PhysicalDeviceTexelBufferAlignmentPropertiesEXT
p Ptr PhysicalDeviceTexelBufferAlignmentPropertiesEXT
-> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr DeviceSize))
    Bool32
uniformTexelBufferOffsetSingleTexelAlignment <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceTexelBufferAlignmentPropertiesEXT
p Ptr PhysicalDeviceTexelBufferAlignmentPropertiesEXT
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr Bool32))
    PhysicalDeviceTexelBufferAlignmentPropertiesEXT
-> IO PhysicalDeviceTexelBufferAlignmentPropertiesEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDeviceTexelBufferAlignmentPropertiesEXT
 -> IO PhysicalDeviceTexelBufferAlignmentPropertiesEXT)
-> PhysicalDeviceTexelBufferAlignmentPropertiesEXT
-> IO PhysicalDeviceTexelBufferAlignmentPropertiesEXT
forall a b. (a -> b) -> a -> b
$ DeviceSize
-> Bool
-> DeviceSize
-> Bool
-> PhysicalDeviceTexelBufferAlignmentPropertiesEXT
PhysicalDeviceTexelBufferAlignmentPropertiesEXT
             DeviceSize
storageTexelBufferOffsetAlignmentBytes (Bool32 -> Bool
bool32ToBool Bool32
storageTexelBufferOffsetSingleTexelAlignment) DeviceSize
uniformTexelBufferOffsetAlignmentBytes (Bool32 -> Bool
bool32ToBool Bool32
uniformTexelBufferOffsetSingleTexelAlignment)

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

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


type EXT_TEXEL_BUFFER_ALIGNMENT_SPEC_VERSION = 1

-- No documentation found for TopLevel "VK_EXT_TEXEL_BUFFER_ALIGNMENT_SPEC_VERSION"
pattern EXT_TEXEL_BUFFER_ALIGNMENT_SPEC_VERSION :: forall a . Integral a => a
pattern $bEXT_TEXEL_BUFFER_ALIGNMENT_SPEC_VERSION :: a
$mEXT_TEXEL_BUFFER_ALIGNMENT_SPEC_VERSION :: forall r a. Integral a => a -> (Void# -> r) -> (Void# -> r) -> r
EXT_TEXEL_BUFFER_ALIGNMENT_SPEC_VERSION = 1


type EXT_TEXEL_BUFFER_ALIGNMENT_EXTENSION_NAME = "VK_EXT_texel_buffer_alignment"

-- No documentation found for TopLevel "VK_EXT_TEXEL_BUFFER_ALIGNMENT_EXTENSION_NAME"
pattern EXT_TEXEL_BUFFER_ALIGNMENT_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bEXT_TEXEL_BUFFER_ALIGNMENT_EXTENSION_NAME :: a
$mEXT_TEXEL_BUFFER_ALIGNMENT_EXTENSION_NAME :: forall r a.
(Eq a, IsString a) =>
a -> (Void# -> r) -> (Void# -> r) -> r
EXT_TEXEL_BUFFER_ALIGNMENT_EXTENSION_NAME = "VK_EXT_texel_buffer_alignment"