{-# language CPP #-}
module Vulkan.Core12.Promoted_From_VK_KHR_buffer_device_address ( getBufferOpaqueCaptureAddress
, getBufferDeviceAddress
, getDeviceMemoryOpaqueCaptureAddress
, PhysicalDeviceBufferDeviceAddressFeatures(..)
, BufferDeviceAddressInfo(..)
, BufferOpaqueCaptureAddressCreateInfo(..)
, MemoryOpaqueCaptureAddressAllocateInfo(..)
, DeviceMemoryOpaqueCaptureAddressInfo(..)
, StructureType(..)
, Result(..)
, BufferUsageFlagBits(..)
, BufferUsageFlags
, BufferCreateFlagBits(..)
, BufferCreateFlags
, MemoryAllocateFlagBits(..)
, MemoryAllocateFlags
) where
import Vulkan.Internal.Utils (traceAroundEvent)
import Control.Monad (unless)
import Control.Monad.IO.Class (liftIO)
import Foreign.Marshal.Alloc (allocaBytes)
import GHC.IO (throwIO)
import GHC.Ptr (nullFunPtr)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Cont (evalContT)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Zero (Zero(..))
import Control.Monad.IO.Class (MonadIO)
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 GHC.IO.Exception (IOErrorType(..))
import GHC.IO.Exception (IOException(..))
import Foreign.Ptr (FunPtr)
import Foreign.Ptr (Ptr)
import Data.Word (Word64)
import Data.Kind (Type)
import Control.Monad.Trans.Cont (ContT(..))
import Vulkan.Core10.FundamentalTypes (bool32ToBool)
import Vulkan.Core10.FundamentalTypes (boolToBool32)
import Vulkan.Core10.FundamentalTypes (Bool32)
import Vulkan.Core10.Handles (Buffer)
import Vulkan.Core10.Handles (Device)
import Vulkan.Core10.Handles (Device(..))
import Vulkan.Core10.Handles (Device(Device))
import Vulkan.Core10.FundamentalTypes (DeviceAddress)
import Vulkan.Dynamic (DeviceCmds(pVkGetBufferDeviceAddress))
import Vulkan.Dynamic (DeviceCmds(pVkGetBufferOpaqueCaptureAddress))
import Vulkan.Dynamic (DeviceCmds(pVkGetDeviceMemoryOpaqueCaptureAddress))
import Vulkan.Core10.Handles (DeviceMemory)
import Vulkan.Core10.Handles (Device_T)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_BUFFER_DEVICE_ADDRESS_INFO))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_BUFFER_OPAQUE_CAPTURE_ADDRESS_CREATE_INFO))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_DEVICE_MEMORY_OPAQUE_CAPTURE_ADDRESS_INFO))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_MEMORY_OPAQUE_CAPTURE_ADDRESS_ALLOCATE_INFO))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_BUFFER_DEVICE_ADDRESS_FEATURES))
import Vulkan.Core10.Enums.BufferCreateFlagBits (BufferCreateFlagBits(..))
import Vulkan.Core10.Enums.BufferCreateFlagBits (BufferCreateFlags)
import Vulkan.Core10.Enums.BufferUsageFlagBits (BufferUsageFlagBits(..))
import Vulkan.Core10.Enums.BufferUsageFlagBits (BufferUsageFlags)
import Vulkan.Core11.Enums.MemoryAllocateFlagBits (MemoryAllocateFlagBits(..))
import Vulkan.Core11.Enums.MemoryAllocateFlagBits (MemoryAllocateFlags)
import Vulkan.Core10.Enums.Result (Result(..))
import Vulkan.Core10.Enums.StructureType (StructureType(..))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkGetBufferOpaqueCaptureAddress
:: FunPtr (Ptr Device_T -> Ptr BufferDeviceAddressInfo -> IO Word64) -> Ptr Device_T -> Ptr BufferDeviceAddressInfo -> IO Word64
getBufferOpaqueCaptureAddress :: forall io
. (MonadIO io)
=>
Device
->
BufferDeviceAddressInfo
-> io (Word64)
getBufferOpaqueCaptureAddress :: forall (io :: * -> *).
MonadIO io =>
Device -> BufferDeviceAddressInfo -> io Word64
getBufferOpaqueCaptureAddress Device
device BufferDeviceAddressInfo
info = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT forall a b. (a -> b) -> a -> b
$ do
let vkGetBufferOpaqueCaptureAddressPtr :: FunPtr
(Ptr Device_T
-> ("pInfo" ::: Ptr BufferDeviceAddressInfo) -> IO Word64)
vkGetBufferOpaqueCaptureAddressPtr = DeviceCmds
-> FunPtr
(Ptr Device_T
-> ("pInfo" ::: Ptr BufferDeviceAddressInfo) -> IO Word64)
pVkGetBufferOpaqueCaptureAddress (case Device
device of Device{DeviceCmds
$sel:deviceCmds:Device :: Device -> DeviceCmds
deviceCmds :: DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
(Ptr Device_T
-> ("pInfo" ::: Ptr BufferDeviceAddressInfo) -> IO Word64)
vkGetBufferOpaqueCaptureAddressPtr forall a. Eq a => a -> a -> Bool
/= forall a. FunPtr a
nullFunPtr) forall a b. (a -> b) -> a -> b
$
forall e a. Exception e => e -> IO a
throwIO forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError forall a. Maybe a
Nothing IOErrorType
InvalidArgument String
"" String
"The function pointer for vkGetBufferOpaqueCaptureAddress is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
let vkGetBufferOpaqueCaptureAddress' :: Ptr Device_T
-> ("pInfo" ::: Ptr BufferDeviceAddressInfo) -> IO Word64
vkGetBufferOpaqueCaptureAddress' = FunPtr
(Ptr Device_T
-> ("pInfo" ::: Ptr BufferDeviceAddressInfo) -> IO Word64)
-> Ptr Device_T
-> ("pInfo" ::: Ptr BufferDeviceAddressInfo)
-> IO Word64
mkVkGetBufferOpaqueCaptureAddress FunPtr
(Ptr Device_T
-> ("pInfo" ::: Ptr BufferDeviceAddressInfo) -> IO Word64)
vkGetBufferOpaqueCaptureAddressPtr
"pInfo" ::: Ptr BufferDeviceAddressInfo
pInfo <- forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (BufferDeviceAddressInfo
info)
Word64
r <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. String -> IO a -> IO a
traceAroundEvent String
"vkGetBufferOpaqueCaptureAddress" (Ptr Device_T
-> ("pInfo" ::: Ptr BufferDeviceAddressInfo) -> IO Word64
vkGetBufferOpaqueCaptureAddress'
(Device -> Ptr Device_T
deviceHandle (Device
device))
"pInfo" ::: Ptr BufferDeviceAddressInfo
pInfo)
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ (Word64
r)
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkGetBufferDeviceAddress
:: FunPtr (Ptr Device_T -> Ptr BufferDeviceAddressInfo -> IO DeviceAddress) -> Ptr Device_T -> Ptr BufferDeviceAddressInfo -> IO DeviceAddress
getBufferDeviceAddress :: forall io
. (MonadIO io)
=>
Device
->
BufferDeviceAddressInfo
-> io (DeviceAddress)
getBufferDeviceAddress :: forall (io :: * -> *).
MonadIO io =>
Device -> BufferDeviceAddressInfo -> io Word64
getBufferDeviceAddress Device
device BufferDeviceAddressInfo
info = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT forall a b. (a -> b) -> a -> b
$ do
let vkGetBufferDeviceAddressPtr :: FunPtr
(Ptr Device_T
-> ("pInfo" ::: Ptr BufferDeviceAddressInfo) -> IO Word64)
vkGetBufferDeviceAddressPtr = DeviceCmds
-> FunPtr
(Ptr Device_T
-> ("pInfo" ::: Ptr BufferDeviceAddressInfo) -> IO Word64)
pVkGetBufferDeviceAddress (case Device
device of Device{DeviceCmds
deviceCmds :: DeviceCmds
$sel:deviceCmds:Device :: Device -> DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
(Ptr Device_T
-> ("pInfo" ::: Ptr BufferDeviceAddressInfo) -> IO Word64)
vkGetBufferDeviceAddressPtr forall a. Eq a => a -> a -> Bool
/= forall a. FunPtr a
nullFunPtr) forall a b. (a -> b) -> a -> b
$
forall e a. Exception e => e -> IO a
throwIO forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError forall a. Maybe a
Nothing IOErrorType
InvalidArgument String
"" String
"The function pointer for vkGetBufferDeviceAddress is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
let vkGetBufferDeviceAddress' :: Ptr Device_T
-> ("pInfo" ::: Ptr BufferDeviceAddressInfo) -> IO Word64
vkGetBufferDeviceAddress' = FunPtr
(Ptr Device_T
-> ("pInfo" ::: Ptr BufferDeviceAddressInfo) -> IO Word64)
-> Ptr Device_T
-> ("pInfo" ::: Ptr BufferDeviceAddressInfo)
-> IO Word64
mkVkGetBufferDeviceAddress FunPtr
(Ptr Device_T
-> ("pInfo" ::: Ptr BufferDeviceAddressInfo) -> IO Word64)
vkGetBufferDeviceAddressPtr
"pInfo" ::: Ptr BufferDeviceAddressInfo
pInfo <- forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (BufferDeviceAddressInfo
info)
Word64
r <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. String -> IO a -> IO a
traceAroundEvent String
"vkGetBufferDeviceAddress" (Ptr Device_T
-> ("pInfo" ::: Ptr BufferDeviceAddressInfo) -> IO Word64
vkGetBufferDeviceAddress'
(Device -> Ptr Device_T
deviceHandle (Device
device))
"pInfo" ::: Ptr BufferDeviceAddressInfo
pInfo)
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ (Word64
r)
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkGetDeviceMemoryOpaqueCaptureAddress
:: FunPtr (Ptr Device_T -> Ptr DeviceMemoryOpaqueCaptureAddressInfo -> IO Word64) -> Ptr Device_T -> Ptr DeviceMemoryOpaqueCaptureAddressInfo -> IO Word64
getDeviceMemoryOpaqueCaptureAddress :: forall io
. (MonadIO io)
=>
Device
->
DeviceMemoryOpaqueCaptureAddressInfo
-> io (Word64)
getDeviceMemoryOpaqueCaptureAddress :: forall (io :: * -> *).
MonadIO io =>
Device -> DeviceMemoryOpaqueCaptureAddressInfo -> io Word64
getDeviceMemoryOpaqueCaptureAddress Device
device DeviceMemoryOpaqueCaptureAddressInfo
info = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT forall a b. (a -> b) -> a -> b
$ do
let vkGetDeviceMemoryOpaqueCaptureAddressPtr :: FunPtr
(Ptr Device_T
-> ("pInfo" ::: Ptr DeviceMemoryOpaqueCaptureAddressInfo)
-> IO Word64)
vkGetDeviceMemoryOpaqueCaptureAddressPtr = DeviceCmds
-> FunPtr
(Ptr Device_T
-> ("pInfo" ::: Ptr DeviceMemoryOpaqueCaptureAddressInfo)
-> IO Word64)
pVkGetDeviceMemoryOpaqueCaptureAddress (case Device
device of Device{DeviceCmds
deviceCmds :: DeviceCmds
$sel:deviceCmds:Device :: Device -> DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
(Ptr Device_T
-> ("pInfo" ::: Ptr DeviceMemoryOpaqueCaptureAddressInfo)
-> IO Word64)
vkGetDeviceMemoryOpaqueCaptureAddressPtr forall a. Eq a => a -> a -> Bool
/= forall a. FunPtr a
nullFunPtr) forall a b. (a -> b) -> a -> b
$
forall e a. Exception e => e -> IO a
throwIO forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError forall a. Maybe a
Nothing IOErrorType
InvalidArgument String
"" String
"The function pointer for vkGetDeviceMemoryOpaqueCaptureAddress is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
let vkGetDeviceMemoryOpaqueCaptureAddress' :: Ptr Device_T
-> ("pInfo" ::: Ptr DeviceMemoryOpaqueCaptureAddressInfo)
-> IO Word64
vkGetDeviceMemoryOpaqueCaptureAddress' = FunPtr
(Ptr Device_T
-> ("pInfo" ::: Ptr DeviceMemoryOpaqueCaptureAddressInfo)
-> IO Word64)
-> Ptr Device_T
-> ("pInfo" ::: Ptr DeviceMemoryOpaqueCaptureAddressInfo)
-> IO Word64
mkVkGetDeviceMemoryOpaqueCaptureAddress FunPtr
(Ptr Device_T
-> ("pInfo" ::: Ptr DeviceMemoryOpaqueCaptureAddressInfo)
-> IO Word64)
vkGetDeviceMemoryOpaqueCaptureAddressPtr
"pInfo" ::: Ptr DeviceMemoryOpaqueCaptureAddressInfo
pInfo <- forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (DeviceMemoryOpaqueCaptureAddressInfo
info)
Word64
r <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. String -> IO a -> IO a
traceAroundEvent String
"vkGetDeviceMemoryOpaqueCaptureAddress" (Ptr Device_T
-> ("pInfo" ::: Ptr DeviceMemoryOpaqueCaptureAddressInfo)
-> IO Word64
vkGetDeviceMemoryOpaqueCaptureAddress'
(Device -> Ptr Device_T
deviceHandle (Device
device))
"pInfo" ::: Ptr DeviceMemoryOpaqueCaptureAddressInfo
pInfo)
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ (Word64
r)
data PhysicalDeviceBufferDeviceAddressFeatures = PhysicalDeviceBufferDeviceAddressFeatures
{
PhysicalDeviceBufferDeviceAddressFeatures -> Bool
bufferDeviceAddress :: Bool
,
PhysicalDeviceBufferDeviceAddressFeatures -> Bool
bufferDeviceAddressCaptureReplay :: Bool
,
PhysicalDeviceBufferDeviceAddressFeatures -> Bool
bufferDeviceAddressMultiDevice :: Bool
}
deriving (Typeable, PhysicalDeviceBufferDeviceAddressFeatures
-> PhysicalDeviceBufferDeviceAddressFeatures -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceBufferDeviceAddressFeatures
-> PhysicalDeviceBufferDeviceAddressFeatures -> Bool
$c/= :: PhysicalDeviceBufferDeviceAddressFeatures
-> PhysicalDeviceBufferDeviceAddressFeatures -> Bool
== :: PhysicalDeviceBufferDeviceAddressFeatures
-> PhysicalDeviceBufferDeviceAddressFeatures -> Bool
$c== :: PhysicalDeviceBufferDeviceAddressFeatures
-> PhysicalDeviceBufferDeviceAddressFeatures -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceBufferDeviceAddressFeatures)
#endif
deriving instance Show PhysicalDeviceBufferDeviceAddressFeatures
instance ToCStruct PhysicalDeviceBufferDeviceAddressFeatures where
withCStruct :: forall b.
PhysicalDeviceBufferDeviceAddressFeatures
-> (Ptr PhysicalDeviceBufferDeviceAddressFeatures -> IO b) -> IO b
withCStruct PhysicalDeviceBufferDeviceAddressFeatures
x Ptr PhysicalDeviceBufferDeviceAddressFeatures -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
32 forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceBufferDeviceAddressFeatures
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceBufferDeviceAddressFeatures
p PhysicalDeviceBufferDeviceAddressFeatures
x (Ptr PhysicalDeviceBufferDeviceAddressFeatures -> IO b
f Ptr PhysicalDeviceBufferDeviceAddressFeatures
p)
pokeCStruct :: forall b.
Ptr PhysicalDeviceBufferDeviceAddressFeatures
-> PhysicalDeviceBufferDeviceAddressFeatures -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceBufferDeviceAddressFeatures
p PhysicalDeviceBufferDeviceAddressFeatures{Bool
bufferDeviceAddressMultiDevice :: Bool
bufferDeviceAddressCaptureReplay :: Bool
bufferDeviceAddress :: Bool
$sel:bufferDeviceAddressMultiDevice:PhysicalDeviceBufferDeviceAddressFeatures :: PhysicalDeviceBufferDeviceAddressFeatures -> Bool
$sel:bufferDeviceAddressCaptureReplay:PhysicalDeviceBufferDeviceAddressFeatures :: PhysicalDeviceBufferDeviceAddressFeatures -> Bool
$sel:bufferDeviceAddress:PhysicalDeviceBufferDeviceAddressFeatures :: PhysicalDeviceBufferDeviceAddressFeatures -> Bool
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceBufferDeviceAddressFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_BUFFER_DEVICE_ADDRESS_FEATURES)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceBufferDeviceAddressFeatures
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 PhysicalDeviceBufferDeviceAddressFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
bufferDeviceAddress))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceBufferDeviceAddressFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
bufferDeviceAddressCaptureReplay))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceBufferDeviceAddressFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
bufferDeviceAddressMultiDevice))
IO b
f
cStructSize :: Int
cStructSize = Int
32
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
Ptr PhysicalDeviceBufferDeviceAddressFeatures -> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceBufferDeviceAddressFeatures
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceBufferDeviceAddressFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_BUFFER_DEVICE_ADDRESS_FEATURES)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceBufferDeviceAddressFeatures
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 PhysicalDeviceBufferDeviceAddressFeatures
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 PhysicalDeviceBufferDeviceAddressFeatures
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 PhysicalDeviceBufferDeviceAddressFeatures
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 PhysicalDeviceBufferDeviceAddressFeatures where
peekCStruct :: Ptr PhysicalDeviceBufferDeviceAddressFeatures
-> IO PhysicalDeviceBufferDeviceAddressFeatures
peekCStruct Ptr PhysicalDeviceBufferDeviceAddressFeatures
p = do
Bool32
bufferDeviceAddress <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceBufferDeviceAddressFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32))
Bool32
bufferDeviceAddressCaptureReplay <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceBufferDeviceAddressFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32))
Bool32
bufferDeviceAddressMultiDevice <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceBufferDeviceAddressFeatures
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 -> PhysicalDeviceBufferDeviceAddressFeatures
PhysicalDeviceBufferDeviceAddressFeatures
(Bool32 -> Bool
bool32ToBool Bool32
bufferDeviceAddress)
(Bool32 -> Bool
bool32ToBool Bool32
bufferDeviceAddressCaptureReplay)
(Bool32 -> Bool
bool32ToBool Bool32
bufferDeviceAddressMultiDevice)
instance Storable PhysicalDeviceBufferDeviceAddressFeatures where
sizeOf :: PhysicalDeviceBufferDeviceAddressFeatures -> Int
sizeOf ~PhysicalDeviceBufferDeviceAddressFeatures
_ = Int
32
alignment :: PhysicalDeviceBufferDeviceAddressFeatures -> Int
alignment ~PhysicalDeviceBufferDeviceAddressFeatures
_ = Int
8
peek :: Ptr PhysicalDeviceBufferDeviceAddressFeatures
-> IO PhysicalDeviceBufferDeviceAddressFeatures
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr PhysicalDeviceBufferDeviceAddressFeatures
-> PhysicalDeviceBufferDeviceAddressFeatures -> IO ()
poke Ptr PhysicalDeviceBufferDeviceAddressFeatures
ptr PhysicalDeviceBufferDeviceAddressFeatures
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceBufferDeviceAddressFeatures
ptr PhysicalDeviceBufferDeviceAddressFeatures
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PhysicalDeviceBufferDeviceAddressFeatures where
zero :: PhysicalDeviceBufferDeviceAddressFeatures
zero = Bool -> Bool -> Bool -> PhysicalDeviceBufferDeviceAddressFeatures
PhysicalDeviceBufferDeviceAddressFeatures
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
data BufferDeviceAddressInfo = BufferDeviceAddressInfo
{
BufferDeviceAddressInfo -> Buffer
buffer :: Buffer }
deriving (Typeable, BufferDeviceAddressInfo -> BufferDeviceAddressInfo -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BufferDeviceAddressInfo -> BufferDeviceAddressInfo -> Bool
$c/= :: BufferDeviceAddressInfo -> BufferDeviceAddressInfo -> Bool
== :: BufferDeviceAddressInfo -> BufferDeviceAddressInfo -> Bool
$c== :: BufferDeviceAddressInfo -> BufferDeviceAddressInfo -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (BufferDeviceAddressInfo)
#endif
deriving instance Show BufferDeviceAddressInfo
instance ToCStruct BufferDeviceAddressInfo where
withCStruct :: forall b.
BufferDeviceAddressInfo
-> (("pInfo" ::: Ptr BufferDeviceAddressInfo) -> IO b) -> IO b
withCStruct BufferDeviceAddressInfo
x ("pInfo" ::: Ptr BufferDeviceAddressInfo) -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \"pInfo" ::: Ptr BufferDeviceAddressInfo
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pInfo" ::: Ptr BufferDeviceAddressInfo
p BufferDeviceAddressInfo
x (("pInfo" ::: Ptr BufferDeviceAddressInfo) -> IO b
f "pInfo" ::: Ptr BufferDeviceAddressInfo
p)
pokeCStruct :: forall b.
("pInfo" ::: Ptr BufferDeviceAddressInfo)
-> BufferDeviceAddressInfo -> IO b -> IO b
pokeCStruct "pInfo" ::: Ptr BufferDeviceAddressInfo
p BufferDeviceAddressInfo{Buffer
buffer :: Buffer
$sel:buffer:BufferDeviceAddressInfo :: BufferDeviceAddressInfo -> Buffer
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr BufferDeviceAddressInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_BUFFER_DEVICE_ADDRESS_INFO)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr BufferDeviceAddressInfo
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 (("pInfo" ::: Ptr BufferDeviceAddressInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Buffer)) (Buffer
buffer)
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b. ("pInfo" ::: Ptr BufferDeviceAddressInfo) -> IO b -> IO b
pokeZeroCStruct "pInfo" ::: Ptr BufferDeviceAddressInfo
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr BufferDeviceAddressInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_BUFFER_DEVICE_ADDRESS_INFO)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr BufferDeviceAddressInfo
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 (("pInfo" ::: Ptr BufferDeviceAddressInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Buffer)) (forall a. Zero a => a
zero)
IO b
f
instance FromCStruct BufferDeviceAddressInfo where
peekCStruct :: ("pInfo" ::: Ptr BufferDeviceAddressInfo)
-> IO BufferDeviceAddressInfo
peekCStruct "pInfo" ::: Ptr BufferDeviceAddressInfo
p = do
Buffer
buffer <- forall a. Storable a => Ptr a -> IO a
peek @Buffer (("pInfo" ::: Ptr BufferDeviceAddressInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Buffer))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Buffer -> BufferDeviceAddressInfo
BufferDeviceAddressInfo
Buffer
buffer
instance Storable BufferDeviceAddressInfo where
sizeOf :: BufferDeviceAddressInfo -> Int
sizeOf ~BufferDeviceAddressInfo
_ = Int
24
alignment :: BufferDeviceAddressInfo -> Int
alignment ~BufferDeviceAddressInfo
_ = Int
8
peek :: ("pInfo" ::: Ptr BufferDeviceAddressInfo)
-> IO BufferDeviceAddressInfo
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: ("pInfo" ::: Ptr BufferDeviceAddressInfo)
-> BufferDeviceAddressInfo -> IO ()
poke "pInfo" ::: Ptr BufferDeviceAddressInfo
ptr BufferDeviceAddressInfo
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pInfo" ::: Ptr BufferDeviceAddressInfo
ptr BufferDeviceAddressInfo
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero BufferDeviceAddressInfo where
zero :: BufferDeviceAddressInfo
zero = Buffer -> BufferDeviceAddressInfo
BufferDeviceAddressInfo
forall a. Zero a => a
zero
data BufferOpaqueCaptureAddressCreateInfo = BufferOpaqueCaptureAddressCreateInfo
{
BufferOpaqueCaptureAddressCreateInfo -> Word64
opaqueCaptureAddress :: Word64 }
deriving (Typeable, BufferOpaqueCaptureAddressCreateInfo
-> BufferOpaqueCaptureAddressCreateInfo -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BufferOpaqueCaptureAddressCreateInfo
-> BufferOpaqueCaptureAddressCreateInfo -> Bool
$c/= :: BufferOpaqueCaptureAddressCreateInfo
-> BufferOpaqueCaptureAddressCreateInfo -> Bool
== :: BufferOpaqueCaptureAddressCreateInfo
-> BufferOpaqueCaptureAddressCreateInfo -> Bool
$c== :: BufferOpaqueCaptureAddressCreateInfo
-> BufferOpaqueCaptureAddressCreateInfo -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (BufferOpaqueCaptureAddressCreateInfo)
#endif
deriving instance Show BufferOpaqueCaptureAddressCreateInfo
instance ToCStruct BufferOpaqueCaptureAddressCreateInfo where
withCStruct :: forall b.
BufferOpaqueCaptureAddressCreateInfo
-> (Ptr BufferOpaqueCaptureAddressCreateInfo -> IO b) -> IO b
withCStruct BufferOpaqueCaptureAddressCreateInfo
x Ptr BufferOpaqueCaptureAddressCreateInfo -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr BufferOpaqueCaptureAddressCreateInfo
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr BufferOpaqueCaptureAddressCreateInfo
p BufferOpaqueCaptureAddressCreateInfo
x (Ptr BufferOpaqueCaptureAddressCreateInfo -> IO b
f Ptr BufferOpaqueCaptureAddressCreateInfo
p)
pokeCStruct :: forall b.
Ptr BufferOpaqueCaptureAddressCreateInfo
-> BufferOpaqueCaptureAddressCreateInfo -> IO b -> IO b
pokeCStruct Ptr BufferOpaqueCaptureAddressCreateInfo
p BufferOpaqueCaptureAddressCreateInfo{Word64
opaqueCaptureAddress :: Word64
$sel:opaqueCaptureAddress:BufferOpaqueCaptureAddressCreateInfo :: BufferOpaqueCaptureAddressCreateInfo -> Word64
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr BufferOpaqueCaptureAddressCreateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_BUFFER_OPAQUE_CAPTURE_ADDRESS_CREATE_INFO)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr BufferOpaqueCaptureAddressCreateInfo
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 BufferOpaqueCaptureAddressCreateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word64)) (Word64
opaqueCaptureAddress)
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b. Ptr BufferOpaqueCaptureAddressCreateInfo -> IO b -> IO b
pokeZeroCStruct Ptr BufferOpaqueCaptureAddressCreateInfo
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr BufferOpaqueCaptureAddressCreateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_BUFFER_OPAQUE_CAPTURE_ADDRESS_CREATE_INFO)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr BufferOpaqueCaptureAddressCreateInfo
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 BufferOpaqueCaptureAddressCreateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word64)) (forall a. Zero a => a
zero)
IO b
f
instance FromCStruct BufferOpaqueCaptureAddressCreateInfo where
peekCStruct :: Ptr BufferOpaqueCaptureAddressCreateInfo
-> IO BufferOpaqueCaptureAddressCreateInfo
peekCStruct Ptr BufferOpaqueCaptureAddressCreateInfo
p = do
Word64
opaqueCaptureAddress <- forall a. Storable a => Ptr a -> IO a
peek @Word64 ((Ptr BufferOpaqueCaptureAddressCreateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word64))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Word64 -> BufferOpaqueCaptureAddressCreateInfo
BufferOpaqueCaptureAddressCreateInfo
Word64
opaqueCaptureAddress
instance Storable BufferOpaqueCaptureAddressCreateInfo where
sizeOf :: BufferOpaqueCaptureAddressCreateInfo -> Int
sizeOf ~BufferOpaqueCaptureAddressCreateInfo
_ = Int
24
alignment :: BufferOpaqueCaptureAddressCreateInfo -> Int
alignment ~BufferOpaqueCaptureAddressCreateInfo
_ = Int
8
peek :: Ptr BufferOpaqueCaptureAddressCreateInfo
-> IO BufferOpaqueCaptureAddressCreateInfo
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr BufferOpaqueCaptureAddressCreateInfo
-> BufferOpaqueCaptureAddressCreateInfo -> IO ()
poke Ptr BufferOpaqueCaptureAddressCreateInfo
ptr BufferOpaqueCaptureAddressCreateInfo
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr BufferOpaqueCaptureAddressCreateInfo
ptr BufferOpaqueCaptureAddressCreateInfo
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero BufferOpaqueCaptureAddressCreateInfo where
zero :: BufferOpaqueCaptureAddressCreateInfo
zero = Word64 -> BufferOpaqueCaptureAddressCreateInfo
BufferOpaqueCaptureAddressCreateInfo
forall a. Zero a => a
zero
data MemoryOpaqueCaptureAddressAllocateInfo = MemoryOpaqueCaptureAddressAllocateInfo
{
MemoryOpaqueCaptureAddressAllocateInfo -> Word64
opaqueCaptureAddress :: Word64 }
deriving (Typeable, MemoryOpaqueCaptureAddressAllocateInfo
-> MemoryOpaqueCaptureAddressAllocateInfo -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MemoryOpaqueCaptureAddressAllocateInfo
-> MemoryOpaqueCaptureAddressAllocateInfo -> Bool
$c/= :: MemoryOpaqueCaptureAddressAllocateInfo
-> MemoryOpaqueCaptureAddressAllocateInfo -> Bool
== :: MemoryOpaqueCaptureAddressAllocateInfo
-> MemoryOpaqueCaptureAddressAllocateInfo -> Bool
$c== :: MemoryOpaqueCaptureAddressAllocateInfo
-> MemoryOpaqueCaptureAddressAllocateInfo -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (MemoryOpaqueCaptureAddressAllocateInfo)
#endif
deriving instance Show MemoryOpaqueCaptureAddressAllocateInfo
instance ToCStruct MemoryOpaqueCaptureAddressAllocateInfo where
withCStruct :: forall b.
MemoryOpaqueCaptureAddressAllocateInfo
-> (Ptr MemoryOpaqueCaptureAddressAllocateInfo -> IO b) -> IO b
withCStruct MemoryOpaqueCaptureAddressAllocateInfo
x Ptr MemoryOpaqueCaptureAddressAllocateInfo -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr MemoryOpaqueCaptureAddressAllocateInfo
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr MemoryOpaqueCaptureAddressAllocateInfo
p MemoryOpaqueCaptureAddressAllocateInfo
x (Ptr MemoryOpaqueCaptureAddressAllocateInfo -> IO b
f Ptr MemoryOpaqueCaptureAddressAllocateInfo
p)
pokeCStruct :: forall b.
Ptr MemoryOpaqueCaptureAddressAllocateInfo
-> MemoryOpaqueCaptureAddressAllocateInfo -> IO b -> IO b
pokeCStruct Ptr MemoryOpaqueCaptureAddressAllocateInfo
p MemoryOpaqueCaptureAddressAllocateInfo{Word64
opaqueCaptureAddress :: Word64
$sel:opaqueCaptureAddress:MemoryOpaqueCaptureAddressAllocateInfo :: MemoryOpaqueCaptureAddressAllocateInfo -> Word64
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MemoryOpaqueCaptureAddressAllocateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_MEMORY_OPAQUE_CAPTURE_ADDRESS_ALLOCATE_INFO)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MemoryOpaqueCaptureAddressAllocateInfo
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 MemoryOpaqueCaptureAddressAllocateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word64)) (Word64
opaqueCaptureAddress)
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
Ptr MemoryOpaqueCaptureAddressAllocateInfo -> IO b -> IO b
pokeZeroCStruct Ptr MemoryOpaqueCaptureAddressAllocateInfo
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MemoryOpaqueCaptureAddressAllocateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_MEMORY_OPAQUE_CAPTURE_ADDRESS_ALLOCATE_INFO)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MemoryOpaqueCaptureAddressAllocateInfo
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 MemoryOpaqueCaptureAddressAllocateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word64)) (forall a. Zero a => a
zero)
IO b
f
instance FromCStruct MemoryOpaqueCaptureAddressAllocateInfo where
peekCStruct :: Ptr MemoryOpaqueCaptureAddressAllocateInfo
-> IO MemoryOpaqueCaptureAddressAllocateInfo
peekCStruct Ptr MemoryOpaqueCaptureAddressAllocateInfo
p = do
Word64
opaqueCaptureAddress <- forall a. Storable a => Ptr a -> IO a
peek @Word64 ((Ptr MemoryOpaqueCaptureAddressAllocateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word64))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Word64 -> MemoryOpaqueCaptureAddressAllocateInfo
MemoryOpaqueCaptureAddressAllocateInfo
Word64
opaqueCaptureAddress
instance Storable MemoryOpaqueCaptureAddressAllocateInfo where
sizeOf :: MemoryOpaqueCaptureAddressAllocateInfo -> Int
sizeOf ~MemoryOpaqueCaptureAddressAllocateInfo
_ = Int
24
alignment :: MemoryOpaqueCaptureAddressAllocateInfo -> Int
alignment ~MemoryOpaqueCaptureAddressAllocateInfo
_ = Int
8
peek :: Ptr MemoryOpaqueCaptureAddressAllocateInfo
-> IO MemoryOpaqueCaptureAddressAllocateInfo
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr MemoryOpaqueCaptureAddressAllocateInfo
-> MemoryOpaqueCaptureAddressAllocateInfo -> IO ()
poke Ptr MemoryOpaqueCaptureAddressAllocateInfo
ptr MemoryOpaqueCaptureAddressAllocateInfo
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr MemoryOpaqueCaptureAddressAllocateInfo
ptr MemoryOpaqueCaptureAddressAllocateInfo
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero MemoryOpaqueCaptureAddressAllocateInfo where
zero :: MemoryOpaqueCaptureAddressAllocateInfo
zero = Word64 -> MemoryOpaqueCaptureAddressAllocateInfo
MemoryOpaqueCaptureAddressAllocateInfo
forall a. Zero a => a
zero
data DeviceMemoryOpaqueCaptureAddressInfo = DeviceMemoryOpaqueCaptureAddressInfo
{
DeviceMemoryOpaqueCaptureAddressInfo -> DeviceMemory
memory :: DeviceMemory }
deriving (Typeable, DeviceMemoryOpaqueCaptureAddressInfo
-> DeviceMemoryOpaqueCaptureAddressInfo -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeviceMemoryOpaqueCaptureAddressInfo
-> DeviceMemoryOpaqueCaptureAddressInfo -> Bool
$c/= :: DeviceMemoryOpaqueCaptureAddressInfo
-> DeviceMemoryOpaqueCaptureAddressInfo -> Bool
== :: DeviceMemoryOpaqueCaptureAddressInfo
-> DeviceMemoryOpaqueCaptureAddressInfo -> Bool
$c== :: DeviceMemoryOpaqueCaptureAddressInfo
-> DeviceMemoryOpaqueCaptureAddressInfo -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (DeviceMemoryOpaqueCaptureAddressInfo)
#endif
deriving instance Show DeviceMemoryOpaqueCaptureAddressInfo
instance ToCStruct DeviceMemoryOpaqueCaptureAddressInfo where
withCStruct :: forall b.
DeviceMemoryOpaqueCaptureAddressInfo
-> (("pInfo" ::: Ptr DeviceMemoryOpaqueCaptureAddressInfo) -> IO b)
-> IO b
withCStruct DeviceMemoryOpaqueCaptureAddressInfo
x ("pInfo" ::: Ptr DeviceMemoryOpaqueCaptureAddressInfo) -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \"pInfo" ::: Ptr DeviceMemoryOpaqueCaptureAddressInfo
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pInfo" ::: Ptr DeviceMemoryOpaqueCaptureAddressInfo
p DeviceMemoryOpaqueCaptureAddressInfo
x (("pInfo" ::: Ptr DeviceMemoryOpaqueCaptureAddressInfo) -> IO b
f "pInfo" ::: Ptr DeviceMemoryOpaqueCaptureAddressInfo
p)
pokeCStruct :: forall b.
("pInfo" ::: Ptr DeviceMemoryOpaqueCaptureAddressInfo)
-> DeviceMemoryOpaqueCaptureAddressInfo -> IO b -> IO b
pokeCStruct "pInfo" ::: Ptr DeviceMemoryOpaqueCaptureAddressInfo
p DeviceMemoryOpaqueCaptureAddressInfo{DeviceMemory
memory :: DeviceMemory
$sel:memory:DeviceMemoryOpaqueCaptureAddressInfo :: DeviceMemoryOpaqueCaptureAddressInfo -> DeviceMemory
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr DeviceMemoryOpaqueCaptureAddressInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DEVICE_MEMORY_OPAQUE_CAPTURE_ADDRESS_INFO)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr DeviceMemoryOpaqueCaptureAddressInfo
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 (("pInfo" ::: Ptr DeviceMemoryOpaqueCaptureAddressInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DeviceMemory)) (DeviceMemory
memory)
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
("pInfo" ::: Ptr DeviceMemoryOpaqueCaptureAddressInfo)
-> IO b -> IO b
pokeZeroCStruct "pInfo" ::: Ptr DeviceMemoryOpaqueCaptureAddressInfo
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr DeviceMemoryOpaqueCaptureAddressInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DEVICE_MEMORY_OPAQUE_CAPTURE_ADDRESS_INFO)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr DeviceMemoryOpaqueCaptureAddressInfo
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 (("pInfo" ::: Ptr DeviceMemoryOpaqueCaptureAddressInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DeviceMemory)) (forall a. Zero a => a
zero)
IO b
f
instance FromCStruct DeviceMemoryOpaqueCaptureAddressInfo where
peekCStruct :: ("pInfo" ::: Ptr DeviceMemoryOpaqueCaptureAddressInfo)
-> IO DeviceMemoryOpaqueCaptureAddressInfo
peekCStruct "pInfo" ::: Ptr DeviceMemoryOpaqueCaptureAddressInfo
p = do
DeviceMemory
memory <- forall a. Storable a => Ptr a -> IO a
peek @DeviceMemory (("pInfo" ::: Ptr DeviceMemoryOpaqueCaptureAddressInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DeviceMemory))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ DeviceMemory -> DeviceMemoryOpaqueCaptureAddressInfo
DeviceMemoryOpaqueCaptureAddressInfo
DeviceMemory
memory
instance Storable DeviceMemoryOpaqueCaptureAddressInfo where
sizeOf :: DeviceMemoryOpaqueCaptureAddressInfo -> Int
sizeOf ~DeviceMemoryOpaqueCaptureAddressInfo
_ = Int
24
alignment :: DeviceMemoryOpaqueCaptureAddressInfo -> Int
alignment ~DeviceMemoryOpaqueCaptureAddressInfo
_ = Int
8
peek :: ("pInfo" ::: Ptr DeviceMemoryOpaqueCaptureAddressInfo)
-> IO DeviceMemoryOpaqueCaptureAddressInfo
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: ("pInfo" ::: Ptr DeviceMemoryOpaqueCaptureAddressInfo)
-> DeviceMemoryOpaqueCaptureAddressInfo -> IO ()
poke "pInfo" ::: Ptr DeviceMemoryOpaqueCaptureAddressInfo
ptr DeviceMemoryOpaqueCaptureAddressInfo
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pInfo" ::: Ptr DeviceMemoryOpaqueCaptureAddressInfo
ptr DeviceMemoryOpaqueCaptureAddressInfo
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero DeviceMemoryOpaqueCaptureAddressInfo where
zero :: DeviceMemoryOpaqueCaptureAddressInfo
zero = DeviceMemory -> DeviceMemoryOpaqueCaptureAddressInfo
DeviceMemoryOpaqueCaptureAddressInfo
forall a. Zero a => a
zero