{-# language CPP #-}
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(..))
data PhysicalDeviceTexelBufferAlignmentProperties = PhysicalDeviceTexelBufferAlignmentProperties
{
PhysicalDeviceTexelBufferAlignmentProperties -> DeviceSize
storageTexelBufferOffsetAlignmentBytes :: DeviceSize
,
PhysicalDeviceTexelBufferAlignmentProperties -> Bool
storageTexelBufferOffsetSingleTexelAlignment :: Bool
,
PhysicalDeviceTexelBufferAlignmentProperties -> DeviceSize
uniformTexelBufferOffsetAlignmentBytes :: DeviceSize
,
PhysicalDeviceTexelBufferAlignmentProperties -> Bool
uniformTexelBufferOffsetSingleTexelAlignment :: Bool
}
deriving (Typeable, PhysicalDeviceTexelBufferAlignmentProperties
-> PhysicalDeviceTexelBufferAlignmentProperties -> Bool
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 = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
48 forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceTexelBufferAlignmentProperties
p -> 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
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceTexelBufferAlignmentProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_TEXEL_BUFFER_ALIGNMENT_PROPERTIES)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceTexelBufferAlignmentProperties
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 PhysicalDeviceTexelBufferAlignmentProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DeviceSize)) (DeviceSize
storageTexelBufferOffsetAlignmentBytes)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceTexelBufferAlignmentProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
storageTexelBufferOffsetSingleTexelAlignment))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceTexelBufferAlignmentProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr DeviceSize)) (DeviceSize
uniformTexelBufferOffsetAlignmentBytes)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceTexelBufferAlignmentProperties
p 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
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceTexelBufferAlignmentProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_TEXEL_BUFFER_ALIGNMENT_PROPERTIES)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceTexelBufferAlignmentProperties
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 PhysicalDeviceTexelBufferAlignmentProperties
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 PhysicalDeviceTexelBufferAlignmentProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceTexelBufferAlignmentProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr DeviceSize)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceTexelBufferAlignmentProperties
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (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 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 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 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 forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr Bool32))
forall (f :: * -> *) a. Applicative f => a -> f a
pure 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 = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr PhysicalDeviceTexelBufferAlignmentProperties
-> PhysicalDeviceTexelBufferAlignmentProperties -> IO ()
poke Ptr PhysicalDeviceTexelBufferAlignmentProperties
ptr PhysicalDeviceTexelBufferAlignmentProperties
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceTexelBufferAlignmentProperties
ptr PhysicalDeviceTexelBufferAlignmentProperties
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PhysicalDeviceTexelBufferAlignmentProperties where
zero :: PhysicalDeviceTexelBufferAlignmentProperties
zero = DeviceSize
-> Bool
-> DeviceSize
-> Bool
-> PhysicalDeviceTexelBufferAlignmentProperties
PhysicalDeviceTexelBufferAlignmentProperties
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero