{-# language CPP #-}
module Vulkan.Extensions.VK_EXT_primitives_generated_query ( PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT(..)
, EXT_PRIMITIVES_GENERATED_QUERY_SPEC_VERSION
, pattern EXT_PRIMITIVES_GENERATED_QUERY_SPEC_VERSION
, EXT_PRIMITIVES_GENERATED_QUERY_EXTENSION_NAME
, pattern EXT_PRIMITIVES_GENERATED_QUERY_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_PRIMITIVES_GENERATED_QUERY_FEATURES_EXT))
data PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT = PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT
{
PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT -> Bool
primitivesGeneratedQuery :: Bool
,
PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT -> Bool
primitivesGeneratedQueryWithRasterizerDiscard :: Bool
,
PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT -> Bool
primitivesGeneratedQueryWithNonZeroStreams :: Bool
}
deriving (Typeable, PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT
-> PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT
-> PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT -> Bool
$c/= :: PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT
-> PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT -> Bool
== :: PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT
-> PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT -> Bool
$c== :: PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT
-> PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT)
#endif
deriving instance Show PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT
instance ToCStruct PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT where
withCStruct :: forall b.
PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT
-> (Ptr PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT -> IO b)
-> IO b
withCStruct PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT
x Ptr PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
32 forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT
p PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT
x (Ptr PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT -> IO b
f Ptr PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT
p)
pokeCStruct :: forall b.
Ptr PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT
-> PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT
-> IO b
-> IO b
pokeCStruct Ptr PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT
p PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT{Bool
primitivesGeneratedQueryWithNonZeroStreams :: Bool
primitivesGeneratedQueryWithRasterizerDiscard :: Bool
primitivesGeneratedQuery :: Bool
$sel:primitivesGeneratedQueryWithNonZeroStreams:PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT :: PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT -> Bool
$sel:primitivesGeneratedQueryWithRasterizerDiscard:PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT :: PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT -> Bool
$sel:primitivesGeneratedQuery:PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT :: PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT -> Bool
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_PRIMITIVES_GENERATED_QUERY_FEATURES_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT
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 PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
primitivesGeneratedQuery))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
primitivesGeneratedQueryWithRasterizerDiscard))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
primitivesGeneratedQueryWithNonZeroStreams))
IO b
f
cStructSize :: Int
cStructSize = Int
32
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
Ptr PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT
-> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_PRIMITIVES_GENERATED_QUERY_FEATURES_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT
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 PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT
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 PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
IO b
f
instance FromCStruct PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT where
peekCStruct :: Ptr PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT
-> IO PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT
peekCStruct Ptr PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT
p = do
Bool32
primitivesGeneratedQuery <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32))
Bool32
primitivesGeneratedQueryWithRasterizerDiscard <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32))
Bool32
primitivesGeneratedQueryWithNonZeroStreams <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Bool32))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Bool
-> Bool
-> Bool
-> PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT
PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT
(Bool32 -> Bool
bool32ToBool Bool32
primitivesGeneratedQuery)
(Bool32 -> Bool
bool32ToBool Bool32
primitivesGeneratedQueryWithRasterizerDiscard)
(Bool32 -> Bool
bool32ToBool Bool32
primitivesGeneratedQueryWithNonZeroStreams)
instance Storable PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT where
sizeOf :: PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT -> Int
sizeOf ~PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT
_ = Int
32
alignment :: PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT -> Int
alignment ~PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT
_ = Int
8
peek :: Ptr PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT
-> IO PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT
-> PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT -> IO ()
poke Ptr PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT
ptr PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT
ptr PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT where
zero :: PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT
zero = Bool
-> Bool
-> Bool
-> PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT
PhysicalDevicePrimitivesGeneratedQueryFeaturesEXT
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
type EXT_PRIMITIVES_GENERATED_QUERY_SPEC_VERSION = 1
pattern EXT_PRIMITIVES_GENERATED_QUERY_SPEC_VERSION :: forall a . Integral a => a
pattern $bEXT_PRIMITIVES_GENERATED_QUERY_SPEC_VERSION :: forall a. Integral a => a
$mEXT_PRIMITIVES_GENERATED_QUERY_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
EXT_PRIMITIVES_GENERATED_QUERY_SPEC_VERSION = 1
type EXT_PRIMITIVES_GENERATED_QUERY_EXTENSION_NAME = "VK_EXT_primitives_generated_query"
pattern EXT_PRIMITIVES_GENERATED_QUERY_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bEXT_PRIMITIVES_GENERATED_QUERY_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
$mEXT_PRIMITIVES_GENERATED_QUERY_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
EXT_PRIMITIVES_GENERATED_QUERY_EXTENSION_NAME = "VK_EXT_primitives_generated_query"