{-# language CPP #-}
module Vulkan.Extensions.VK_EXT_vertex_attribute_divisor ( pattern STRUCTURE_TYPE_PIPELINE_VERTEX_INPUT_DIVISOR_STATE_CREATE_INFO_EXT
, pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_VERTEX_ATTRIBUTE_DIVISOR_FEATURES_EXT
, PhysicalDeviceVertexAttributeDivisorPropertiesEXT(..)
, VertexInputBindingDivisorDescriptionEXT
, PipelineVertexInputDivisorStateCreateInfoEXT
, PhysicalDeviceVertexAttributeDivisorFeaturesEXT
, EXT_VERTEX_ATTRIBUTE_DIVISOR_SPEC_VERSION
, pattern EXT_VERTEX_ATTRIBUTE_DIVISOR_SPEC_VERSION
, EXT_VERTEX_ATTRIBUTE_DIVISOR_EXTENSION_NAME
, pattern EXT_VERTEX_ATTRIBUTE_DIVISOR_EXTENSION_NAME
, VertexInputBindingDivisorDescriptionKHR(..)
, PipelineVertexInputDivisorStateCreateInfoKHR(..)
, PhysicalDeviceVertexAttributeDivisorFeaturesKHR(..)
) 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.Word (Word32)
import Data.Kind (Type)
import Vulkan.Extensions.VK_KHR_vertex_attribute_divisor (PhysicalDeviceVertexAttributeDivisorFeaturesKHR)
import Vulkan.Extensions.VK_KHR_vertex_attribute_divisor (PipelineVertexInputDivisorStateCreateInfoKHR)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Extensions.VK_KHR_vertex_attribute_divisor (VertexInputBindingDivisorDescriptionKHR)
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_VERTEX_ATTRIBUTE_DIVISOR_FEATURES_KHR))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_VERTEX_ATTRIBUTE_DIVISOR_PROPERTIES_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PIPELINE_VERTEX_INPUT_DIVISOR_STATE_CREATE_INFO_KHR))
import Vulkan.Extensions.VK_KHR_vertex_attribute_divisor (PhysicalDeviceVertexAttributeDivisorFeaturesKHR(..))
import Vulkan.Extensions.VK_KHR_vertex_attribute_divisor (PipelineVertexInputDivisorStateCreateInfoKHR(..))
import Vulkan.Extensions.VK_KHR_vertex_attribute_divisor (VertexInputBindingDivisorDescriptionKHR(..))
pattern $bSTRUCTURE_TYPE_PIPELINE_VERTEX_INPUT_DIVISOR_STATE_CREATE_INFO_EXT :: StructureType
$mSTRUCTURE_TYPE_PIPELINE_VERTEX_INPUT_DIVISOR_STATE_CREATE_INFO_EXT :: forall {r}. StructureType -> ((# #) -> r) -> ((# #) -> r) -> r
STRUCTURE_TYPE_PIPELINE_VERTEX_INPUT_DIVISOR_STATE_CREATE_INFO_EXT = STRUCTURE_TYPE_PIPELINE_VERTEX_INPUT_DIVISOR_STATE_CREATE_INFO_KHR
pattern $bSTRUCTURE_TYPE_PHYSICAL_DEVICE_VERTEX_ATTRIBUTE_DIVISOR_FEATURES_EXT :: StructureType
$mSTRUCTURE_TYPE_PHYSICAL_DEVICE_VERTEX_ATTRIBUTE_DIVISOR_FEATURES_EXT :: forall {r}. StructureType -> ((# #) -> r) -> ((# #) -> r) -> r
STRUCTURE_TYPE_PHYSICAL_DEVICE_VERTEX_ATTRIBUTE_DIVISOR_FEATURES_EXT = STRUCTURE_TYPE_PHYSICAL_DEVICE_VERTEX_ATTRIBUTE_DIVISOR_FEATURES_KHR
data PhysicalDeviceVertexAttributeDivisorPropertiesEXT = PhysicalDeviceVertexAttributeDivisorPropertiesEXT
{
PhysicalDeviceVertexAttributeDivisorPropertiesEXT -> Word32
maxVertexAttribDivisor :: Word32 }
deriving (Typeable, PhysicalDeviceVertexAttributeDivisorPropertiesEXT
-> PhysicalDeviceVertexAttributeDivisorPropertiesEXT -> Bool
(PhysicalDeviceVertexAttributeDivisorPropertiesEXT
-> PhysicalDeviceVertexAttributeDivisorPropertiesEXT -> Bool)
-> (PhysicalDeviceVertexAttributeDivisorPropertiesEXT
-> PhysicalDeviceVertexAttributeDivisorPropertiesEXT -> Bool)
-> Eq PhysicalDeviceVertexAttributeDivisorPropertiesEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PhysicalDeviceVertexAttributeDivisorPropertiesEXT
-> PhysicalDeviceVertexAttributeDivisorPropertiesEXT -> Bool
== :: PhysicalDeviceVertexAttributeDivisorPropertiesEXT
-> PhysicalDeviceVertexAttributeDivisorPropertiesEXT -> Bool
$c/= :: PhysicalDeviceVertexAttributeDivisorPropertiesEXT
-> PhysicalDeviceVertexAttributeDivisorPropertiesEXT -> Bool
/= :: PhysicalDeviceVertexAttributeDivisorPropertiesEXT
-> PhysicalDeviceVertexAttributeDivisorPropertiesEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceVertexAttributeDivisorPropertiesEXT)
#endif
deriving instance Show PhysicalDeviceVertexAttributeDivisorPropertiesEXT
instance ToCStruct PhysicalDeviceVertexAttributeDivisorPropertiesEXT where
withCStruct :: forall b.
PhysicalDeviceVertexAttributeDivisorPropertiesEXT
-> (Ptr PhysicalDeviceVertexAttributeDivisorPropertiesEXT -> IO b)
-> IO b
withCStruct PhysicalDeviceVertexAttributeDivisorPropertiesEXT
x Ptr PhysicalDeviceVertexAttributeDivisorPropertiesEXT -> IO b
f = Int
-> (Ptr PhysicalDeviceVertexAttributeDivisorPropertiesEXT -> IO b)
-> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 ((Ptr PhysicalDeviceVertexAttributeDivisorPropertiesEXT -> IO b)
-> IO b)
-> (Ptr PhysicalDeviceVertexAttributeDivisorPropertiesEXT -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceVertexAttributeDivisorPropertiesEXT
p -> Ptr PhysicalDeviceVertexAttributeDivisorPropertiesEXT
-> PhysicalDeviceVertexAttributeDivisorPropertiesEXT
-> IO b
-> IO b
forall b.
Ptr PhysicalDeviceVertexAttributeDivisorPropertiesEXT
-> PhysicalDeviceVertexAttributeDivisorPropertiesEXT
-> IO b
-> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceVertexAttributeDivisorPropertiesEXT
p PhysicalDeviceVertexAttributeDivisorPropertiesEXT
x (Ptr PhysicalDeviceVertexAttributeDivisorPropertiesEXT -> IO b
f Ptr PhysicalDeviceVertexAttributeDivisorPropertiesEXT
p)
pokeCStruct :: forall b.
Ptr PhysicalDeviceVertexAttributeDivisorPropertiesEXT
-> PhysicalDeviceVertexAttributeDivisorPropertiesEXT
-> IO b
-> IO b
pokeCStruct Ptr PhysicalDeviceVertexAttributeDivisorPropertiesEXT
p PhysicalDeviceVertexAttributeDivisorPropertiesEXT{Word32
$sel:maxVertexAttribDivisor:PhysicalDeviceVertexAttributeDivisorPropertiesEXT :: PhysicalDeviceVertexAttributeDivisorPropertiesEXT -> Word32
maxVertexAttribDivisor :: Word32
..} IO b
f = do
Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVertexAttributeDivisorPropertiesEXT
p Ptr PhysicalDeviceVertexAttributeDivisorPropertiesEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_VERTEX_ATTRIBUTE_DIVISOR_PROPERTIES_EXT)
Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVertexAttributeDivisorPropertiesEXT
p Ptr PhysicalDeviceVertexAttributeDivisorPropertiesEXT
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVertexAttributeDivisorPropertiesEXT
p Ptr PhysicalDeviceVertexAttributeDivisorPropertiesEXT
-> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32)) (Word32
maxVertexAttribDivisor)
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
Ptr PhysicalDeviceVertexAttributeDivisorPropertiesEXT
-> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceVertexAttributeDivisorPropertiesEXT
p IO b
f = do
Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVertexAttributeDivisorPropertiesEXT
p Ptr PhysicalDeviceVertexAttributeDivisorPropertiesEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_VERTEX_ATTRIBUTE_DIVISOR_PROPERTIES_EXT)
Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVertexAttributeDivisorPropertiesEXT
p Ptr PhysicalDeviceVertexAttributeDivisorPropertiesEXT
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceVertexAttributeDivisorPropertiesEXT
p Ptr PhysicalDeviceVertexAttributeDivisorPropertiesEXT
-> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
IO b
f
instance FromCStruct PhysicalDeviceVertexAttributeDivisorPropertiesEXT where
peekCStruct :: Ptr PhysicalDeviceVertexAttributeDivisorPropertiesEXT
-> IO PhysicalDeviceVertexAttributeDivisorPropertiesEXT
peekCStruct Ptr PhysicalDeviceVertexAttributeDivisorPropertiesEXT
p = do
Word32
maxVertexAttribDivisor <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceVertexAttributeDivisorPropertiesEXT
p Ptr PhysicalDeviceVertexAttributeDivisorPropertiesEXT
-> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32))
PhysicalDeviceVertexAttributeDivisorPropertiesEXT
-> IO PhysicalDeviceVertexAttributeDivisorPropertiesEXT
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDeviceVertexAttributeDivisorPropertiesEXT
-> IO PhysicalDeviceVertexAttributeDivisorPropertiesEXT)
-> PhysicalDeviceVertexAttributeDivisorPropertiesEXT
-> IO PhysicalDeviceVertexAttributeDivisorPropertiesEXT
forall a b. (a -> b) -> a -> b
$ Word32 -> PhysicalDeviceVertexAttributeDivisorPropertiesEXT
PhysicalDeviceVertexAttributeDivisorPropertiesEXT
Word32
maxVertexAttribDivisor
instance Storable PhysicalDeviceVertexAttributeDivisorPropertiesEXT where
sizeOf :: PhysicalDeviceVertexAttributeDivisorPropertiesEXT -> Int
sizeOf ~PhysicalDeviceVertexAttributeDivisorPropertiesEXT
_ = Int
24
alignment :: PhysicalDeviceVertexAttributeDivisorPropertiesEXT -> Int
alignment ~PhysicalDeviceVertexAttributeDivisorPropertiesEXT
_ = Int
8
peek :: Ptr PhysicalDeviceVertexAttributeDivisorPropertiesEXT
-> IO PhysicalDeviceVertexAttributeDivisorPropertiesEXT
peek = Ptr PhysicalDeviceVertexAttributeDivisorPropertiesEXT
-> IO PhysicalDeviceVertexAttributeDivisorPropertiesEXT
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr PhysicalDeviceVertexAttributeDivisorPropertiesEXT
-> PhysicalDeviceVertexAttributeDivisorPropertiesEXT -> IO ()
poke Ptr PhysicalDeviceVertexAttributeDivisorPropertiesEXT
ptr PhysicalDeviceVertexAttributeDivisorPropertiesEXT
poked = Ptr PhysicalDeviceVertexAttributeDivisorPropertiesEXT
-> PhysicalDeviceVertexAttributeDivisorPropertiesEXT
-> IO ()
-> IO ()
forall b.
Ptr PhysicalDeviceVertexAttributeDivisorPropertiesEXT
-> PhysicalDeviceVertexAttributeDivisorPropertiesEXT
-> IO b
-> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceVertexAttributeDivisorPropertiesEXT
ptr PhysicalDeviceVertexAttributeDivisorPropertiesEXT
poked (() -> IO ()
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PhysicalDeviceVertexAttributeDivisorPropertiesEXT where
zero :: PhysicalDeviceVertexAttributeDivisorPropertiesEXT
zero = Word32 -> PhysicalDeviceVertexAttributeDivisorPropertiesEXT
PhysicalDeviceVertexAttributeDivisorPropertiesEXT
Word32
forall a. Zero a => a
zero
type VertexInputBindingDivisorDescriptionEXT = VertexInputBindingDivisorDescriptionKHR
type PipelineVertexInputDivisorStateCreateInfoEXT = PipelineVertexInputDivisorStateCreateInfoKHR
type PhysicalDeviceVertexAttributeDivisorFeaturesEXT = PhysicalDeviceVertexAttributeDivisorFeaturesKHR
type EXT_VERTEX_ATTRIBUTE_DIVISOR_SPEC_VERSION = 3
pattern EXT_VERTEX_ATTRIBUTE_DIVISOR_SPEC_VERSION :: forall a . Integral a => a
pattern $bEXT_VERTEX_ATTRIBUTE_DIVISOR_SPEC_VERSION :: forall a. Integral a => a
$mEXT_VERTEX_ATTRIBUTE_DIVISOR_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
EXT_VERTEX_ATTRIBUTE_DIVISOR_SPEC_VERSION = 3
type EXT_VERTEX_ATTRIBUTE_DIVISOR_EXTENSION_NAME = "VK_EXT_vertex_attribute_divisor"
pattern EXT_VERTEX_ATTRIBUTE_DIVISOR_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bEXT_VERTEX_ATTRIBUTE_DIVISOR_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
$mEXT_VERTEX_ATTRIBUTE_DIVISOR_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
EXT_VERTEX_ATTRIBUTE_DIVISOR_EXTENSION_NAME = "VK_EXT_vertex_attribute_divisor"