{-# language CPP #-}
module Vulkan.Extensions.VK_NV_low_latency ( QueryLowLatencySupportNV(..)
, NV_LOW_LATENCY_SPEC_VERSION
, pattern NV_LOW_LATENCY_SPEC_VERSION
, NV_LOW_LATENCY_EXTENSION_NAME
, pattern NV_LOW_LATENCY_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.Enums.StructureType (StructureType)
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_QUERY_LOW_LATENCY_SUPPORT_NV))
data QueryLowLatencySupportNV = QueryLowLatencySupportNV
{
QueryLowLatencySupportNV -> Ptr ()
queriedLowLatencyData :: Ptr () }
deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (QueryLowLatencySupportNV)
#endif
deriving instance Show QueryLowLatencySupportNV
instance ToCStruct QueryLowLatencySupportNV where
withCStruct :: forall b.
QueryLowLatencySupportNV
-> (Ptr QueryLowLatencySupportNV -> IO b) -> IO b
withCStruct QueryLowLatencySupportNV
x Ptr QueryLowLatencySupportNV -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr QueryLowLatencySupportNV
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr QueryLowLatencySupportNV
p QueryLowLatencySupportNV
x (Ptr QueryLowLatencySupportNV -> IO b
f Ptr QueryLowLatencySupportNV
p)
pokeCStruct :: forall b.
Ptr QueryLowLatencySupportNV
-> QueryLowLatencySupportNV -> IO b -> IO b
pokeCStruct Ptr QueryLowLatencySupportNV
p QueryLowLatencySupportNV{Ptr ()
queriedLowLatencyData :: Ptr ()
$sel:queriedLowLatencyData:QueryLowLatencySupportNV :: QueryLowLatencySupportNV -> Ptr ()
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr QueryLowLatencySupportNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_QUERY_LOW_LATENCY_SUPPORT_NV)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr QueryLowLatencySupportNV
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 QueryLowLatencySupportNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr (Ptr ()))) (Ptr ()
queriedLowLatencyData)
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b. Ptr QueryLowLatencySupportNV -> IO b -> IO b
pokeZeroCStruct Ptr QueryLowLatencySupportNV
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr QueryLowLatencySupportNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_QUERY_LOW_LATENCY_SUPPORT_NV)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr QueryLowLatencySupportNV
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 QueryLowLatencySupportNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr (Ptr ()))) (forall a. Zero a => a
zero)
IO b
f
instance FromCStruct QueryLowLatencySupportNV where
peekCStruct :: Ptr QueryLowLatencySupportNV -> IO QueryLowLatencySupportNV
peekCStruct Ptr QueryLowLatencySupportNV
p = do
Ptr ()
pQueriedLowLatencyData <- forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) ((Ptr QueryLowLatencySupportNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr (Ptr ())))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Ptr () -> QueryLowLatencySupportNV
QueryLowLatencySupportNV
Ptr ()
pQueriedLowLatencyData
instance Storable QueryLowLatencySupportNV where
sizeOf :: QueryLowLatencySupportNV -> Int
sizeOf ~QueryLowLatencySupportNV
_ = Int
24
alignment :: QueryLowLatencySupportNV -> Int
alignment ~QueryLowLatencySupportNV
_ = Int
8
peek :: Ptr QueryLowLatencySupportNV -> IO QueryLowLatencySupportNV
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr QueryLowLatencySupportNV -> QueryLowLatencySupportNV -> IO ()
poke Ptr QueryLowLatencySupportNV
ptr QueryLowLatencySupportNV
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr QueryLowLatencySupportNV
ptr QueryLowLatencySupportNV
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero QueryLowLatencySupportNV where
zero :: QueryLowLatencySupportNV
zero = Ptr () -> QueryLowLatencySupportNV
QueryLowLatencySupportNV
forall a. Zero a => a
zero
type NV_LOW_LATENCY_SPEC_VERSION = 1
pattern NV_LOW_LATENCY_SPEC_VERSION :: forall a . Integral a => a
pattern $bNV_LOW_LATENCY_SPEC_VERSION :: forall a. Integral a => a
$mNV_LOW_LATENCY_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
NV_LOW_LATENCY_SPEC_VERSION = 1
type NV_LOW_LATENCY_EXTENSION_NAME = "VK_NV_low_latency"
pattern NV_LOW_LATENCY_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bNV_LOW_LATENCY_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
$mNV_LOW_LATENCY_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
NV_LOW_LATENCY_EXTENSION_NAME = "VK_NV_low_latency"