{-# language CPP #-}
module Vulkan.Extensions.VK_EXT_primitive_topology_list_restart ( PhysicalDevicePrimitiveTopologyListRestartFeaturesEXT(..)
, EXT_PRIMITIVE_TOPOLOGY_LIST_RESTART_SPEC_VERSION
, pattern EXT_PRIMITIVE_TOPOLOGY_LIST_RESTART_SPEC_VERSION
, EXT_PRIMITIVE_TOPOLOGY_LIST_RESTART_EXTENSION_NAME
, pattern EXT_PRIMITIVE_TOPOLOGY_LIST_RESTART_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.Enums.StructureType (StructureType)
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_PRIMITIVE_TOPOLOGY_LIST_RESTART_FEATURES_EXT))
data PhysicalDevicePrimitiveTopologyListRestartFeaturesEXT = PhysicalDevicePrimitiveTopologyListRestartFeaturesEXT
{
PhysicalDevicePrimitiveTopologyListRestartFeaturesEXT -> Bool
primitiveTopologyListRestart :: Bool
,
PhysicalDevicePrimitiveTopologyListRestartFeaturesEXT -> Bool
primitiveTopologyPatchListRestart :: Bool
}
deriving (Typeable, PhysicalDevicePrimitiveTopologyListRestartFeaturesEXT
-> PhysicalDevicePrimitiveTopologyListRestartFeaturesEXT -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDevicePrimitiveTopologyListRestartFeaturesEXT
-> PhysicalDevicePrimitiveTopologyListRestartFeaturesEXT -> Bool
$c/= :: PhysicalDevicePrimitiveTopologyListRestartFeaturesEXT
-> PhysicalDevicePrimitiveTopologyListRestartFeaturesEXT -> Bool
== :: PhysicalDevicePrimitiveTopologyListRestartFeaturesEXT
-> PhysicalDevicePrimitiveTopologyListRestartFeaturesEXT -> Bool
$c== :: PhysicalDevicePrimitiveTopologyListRestartFeaturesEXT
-> PhysicalDevicePrimitiveTopologyListRestartFeaturesEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDevicePrimitiveTopologyListRestartFeaturesEXT)
#endif
deriving instance Show PhysicalDevicePrimitiveTopologyListRestartFeaturesEXT
instance ToCStruct PhysicalDevicePrimitiveTopologyListRestartFeaturesEXT where
withCStruct :: forall b.
PhysicalDevicePrimitiveTopologyListRestartFeaturesEXT
-> (Ptr PhysicalDevicePrimitiveTopologyListRestartFeaturesEXT
-> IO b)
-> IO b
withCStruct PhysicalDevicePrimitiveTopologyListRestartFeaturesEXT
x Ptr PhysicalDevicePrimitiveTopologyListRestartFeaturesEXT -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDevicePrimitiveTopologyListRestartFeaturesEXT
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDevicePrimitiveTopologyListRestartFeaturesEXT
p PhysicalDevicePrimitiveTopologyListRestartFeaturesEXT
x (Ptr PhysicalDevicePrimitiveTopologyListRestartFeaturesEXT -> IO b
f Ptr PhysicalDevicePrimitiveTopologyListRestartFeaturesEXT
p)
pokeCStruct :: forall b.
Ptr PhysicalDevicePrimitiveTopologyListRestartFeaturesEXT
-> PhysicalDevicePrimitiveTopologyListRestartFeaturesEXT
-> IO b
-> IO b
pokeCStruct Ptr PhysicalDevicePrimitiveTopologyListRestartFeaturesEXT
p PhysicalDevicePrimitiveTopologyListRestartFeaturesEXT{Bool
primitiveTopologyPatchListRestart :: Bool
primitiveTopologyListRestart :: Bool
$sel:primitiveTopologyPatchListRestart:PhysicalDevicePrimitiveTopologyListRestartFeaturesEXT :: PhysicalDevicePrimitiveTopologyListRestartFeaturesEXT -> Bool
$sel:primitiveTopologyListRestart:PhysicalDevicePrimitiveTopologyListRestartFeaturesEXT :: PhysicalDevicePrimitiveTopologyListRestartFeaturesEXT -> Bool
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePrimitiveTopologyListRestartFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_PRIMITIVE_TOPOLOGY_LIST_RESTART_FEATURES_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePrimitiveTopologyListRestartFeaturesEXT
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 PhysicalDevicePrimitiveTopologyListRestartFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
primitiveTopologyListRestart))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePrimitiveTopologyListRestartFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
primitiveTopologyPatchListRestart))
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
Ptr PhysicalDevicePrimitiveTopologyListRestartFeaturesEXT
-> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDevicePrimitiveTopologyListRestartFeaturesEXT
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePrimitiveTopologyListRestartFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_PRIMITIVE_TOPOLOGY_LIST_RESTART_FEATURES_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePrimitiveTopologyListRestartFeaturesEXT
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 PhysicalDevicePrimitiveTopologyListRestartFeaturesEXT
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 PhysicalDevicePrimitiveTopologyListRestartFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
IO b
f
instance FromCStruct PhysicalDevicePrimitiveTopologyListRestartFeaturesEXT where
peekCStruct :: Ptr PhysicalDevicePrimitiveTopologyListRestartFeaturesEXT
-> IO PhysicalDevicePrimitiveTopologyListRestartFeaturesEXT
peekCStruct Ptr PhysicalDevicePrimitiveTopologyListRestartFeaturesEXT
p = do
Bool32
primitiveTopologyListRestart <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDevicePrimitiveTopologyListRestartFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32))
Bool32
primitiveTopologyPatchListRestart <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDevicePrimitiveTopologyListRestartFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Bool
-> Bool -> PhysicalDevicePrimitiveTopologyListRestartFeaturesEXT
PhysicalDevicePrimitiveTopologyListRestartFeaturesEXT
(Bool32 -> Bool
bool32ToBool Bool32
primitiveTopologyListRestart)
(Bool32 -> Bool
bool32ToBool Bool32
primitiveTopologyPatchListRestart)
instance Storable PhysicalDevicePrimitiveTopologyListRestartFeaturesEXT where
sizeOf :: PhysicalDevicePrimitiveTopologyListRestartFeaturesEXT -> Int
sizeOf ~PhysicalDevicePrimitiveTopologyListRestartFeaturesEXT
_ = Int
24
alignment :: PhysicalDevicePrimitiveTopologyListRestartFeaturesEXT -> Int
alignment ~PhysicalDevicePrimitiveTopologyListRestartFeaturesEXT
_ = Int
8
peek :: Ptr PhysicalDevicePrimitiveTopologyListRestartFeaturesEXT
-> IO PhysicalDevicePrimitiveTopologyListRestartFeaturesEXT
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr PhysicalDevicePrimitiveTopologyListRestartFeaturesEXT
-> PhysicalDevicePrimitiveTopologyListRestartFeaturesEXT -> IO ()
poke Ptr PhysicalDevicePrimitiveTopologyListRestartFeaturesEXT
ptr PhysicalDevicePrimitiveTopologyListRestartFeaturesEXT
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDevicePrimitiveTopologyListRestartFeaturesEXT
ptr PhysicalDevicePrimitiveTopologyListRestartFeaturesEXT
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PhysicalDevicePrimitiveTopologyListRestartFeaturesEXT where
zero :: PhysicalDevicePrimitiveTopologyListRestartFeaturesEXT
zero = Bool
-> Bool -> PhysicalDevicePrimitiveTopologyListRestartFeaturesEXT
PhysicalDevicePrimitiveTopologyListRestartFeaturesEXT
forall a. Zero a => a
zero
forall a. Zero a => a
zero
type EXT_PRIMITIVE_TOPOLOGY_LIST_RESTART_SPEC_VERSION = 1
pattern EXT_PRIMITIVE_TOPOLOGY_LIST_RESTART_SPEC_VERSION :: forall a . Integral a => a
pattern $bEXT_PRIMITIVE_TOPOLOGY_LIST_RESTART_SPEC_VERSION :: forall a. Integral a => a
$mEXT_PRIMITIVE_TOPOLOGY_LIST_RESTART_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
EXT_PRIMITIVE_TOPOLOGY_LIST_RESTART_SPEC_VERSION = 1
type EXT_PRIMITIVE_TOPOLOGY_LIST_RESTART_EXTENSION_NAME = "VK_EXT_primitive_topology_list_restart"
pattern EXT_PRIMITIVE_TOPOLOGY_LIST_RESTART_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bEXT_PRIMITIVE_TOPOLOGY_LIST_RESTART_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
$mEXT_PRIMITIVE_TOPOLOGY_LIST_RESTART_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
EXT_PRIMITIVE_TOPOLOGY_LIST_RESTART_EXTENSION_NAME = "VK_EXT_primitive_topology_list_restart"