{-# language CPP #-}
-- No documentation found for Chapter "Promoted_From_VK_EXT_texel_buffer_alignment"
module Vulkan.Core13.Promoted_From_VK_EXT_texel_buffer_alignment  ( PhysicalDeviceTexelBufferAlignmentProperties(..)
                                                                  , StructureType(..)
                                                                  ) 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.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_TEXEL_BUFFER_ALIGNMENT_PROPERTIES))
import Vulkan.Core10.Enums.StructureType (StructureType(..))
-- | VkPhysicalDeviceTexelBufferAlignmentProperties - Structure describing
-- the texel buffer alignment requirements supported by an implementation
--
-- = Description
--
-- If the 'PhysicalDeviceTexelBufferAlignmentProperties' 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.
--
-- 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://registry.khronos.org/vulkan/specs/1.3-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
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_texel_buffer_alignment VK_EXT_texel_buffer_alignment>,
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_3 VK_VERSION_1_3>,
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.FundamentalTypes.DeviceSize',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDeviceTexelBufferAlignmentProperties = PhysicalDeviceTexelBufferAlignmentProperties
  { -- | #extension-limits-storageTexelBufferOffsetAlignmentBytes#
    -- @storageTexelBufferOffsetAlignmentBytes@ is a byte alignment that is
    -- sufficient for a storage texel buffer of any format. The value /must/ be
    -- a power of two.
    PhysicalDeviceTexelBufferAlignmentProperties -> DeviceSize
storageTexelBufferOffsetAlignmentBytes :: DeviceSize
  , -- | #extension-limits-storageTexelBufferOffsetSingleTexelAlignment#
    -- @storageTexelBufferOffsetSingleTexelAlignment@ indicates whether single
    -- texel alignment is sufficient for a storage texel buffer of any format.
    PhysicalDeviceTexelBufferAlignmentProperties -> Bool
storageTexelBufferOffsetSingleTexelAlignment :: Bool
  , -- | #extension-limits-uniformTexelBufferOffsetAlignmentBytes#
    -- @uniformTexelBufferOffsetAlignmentBytes@ is a byte alignment that is
    -- sufficient for a uniform texel buffer of any format. The value /must/ be
    -- a power of two.
    PhysicalDeviceTexelBufferAlignmentProperties -> DeviceSize
uniformTexelBufferOffsetAlignmentBytes :: DeviceSize
  , -- | #extension-limits-uniformTexelBufferOffsetSingleTexelAlignment#
    -- @uniformTexelBufferOffsetSingleTexelAlignment@ indicates whether single
    -- texel alignment is sufficient for a uniform texel buffer of any format.
    PhysicalDeviceTexelBufferAlignmentProperties -> Bool
uniformTexelBufferOffsetSingleTexelAlignment :: Bool
  }
  deriving (Typeable, PhysicalDeviceTexelBufferAlignmentProperties
-> PhysicalDeviceTexelBufferAlignmentProperties -> Bool
(PhysicalDeviceTexelBufferAlignmentProperties
 -> PhysicalDeviceTexelBufferAlignmentProperties -> Bool)
-> (PhysicalDeviceTexelBufferAlignmentProperties
    -> PhysicalDeviceTexelBufferAlignmentProperties -> Bool)
-> Eq PhysicalDeviceTexelBufferAlignmentProperties
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceTexelBufferAlignmentProperties
-> PhysicalDeviceTexelBufferAlignmentProperties -> Bool
$c/= :: PhysicalDeviceTexelBufferAlignmentProperties
-> PhysicalDeviceTexelBufferAlignmentProperties -> Bool
== :: PhysicalDeviceTexelBufferAlignmentProperties
-> PhysicalDeviceTexelBufferAlignmentProperties -> Bool
$c== :: PhysicalDeviceTexelBufferAlignmentProperties
-> PhysicalDeviceTexelBufferAlignmentProperties -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceTexelBufferAlignmentProperties)
#endif
deriving instance Show PhysicalDeviceTexelBufferAlignmentProperties

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

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

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

instance Zero PhysicalDeviceTexelBufferAlignmentProperties where
  zero :: PhysicalDeviceTexelBufferAlignmentProperties
zero = DeviceSize
-> Bool
-> DeviceSize
-> Bool
-> PhysicalDeviceTexelBufferAlignmentProperties
PhysicalDeviceTexelBufferAlignmentProperties
           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