{-# language CPP #-}
module Vulkan.Core13.Promoted_From_VK_EXT_private_data ( createPrivateDataSlot
, withPrivateDataSlot
, destroyPrivateDataSlot
, setPrivateData
, getPrivateData
, DevicePrivateDataCreateInfo(..)
, PrivateDataSlotCreateInfo(..)
, PhysicalDevicePrivateDataFeatures(..)
, PrivateDataSlot(..)
, PrivateDataSlotCreateFlags(..)
, StructureType(..)
, ObjectType(..)
) where
import Vulkan.Internal.Utils (traceAroundEvent)
import Control.Exception.Base (bracket)
import Control.Monad (unless)
import Control.Monad.IO.Class (liftIO)
import Foreign.Marshal.Alloc (allocaBytes)
import Foreign.Marshal.Alloc (callocBytes)
import Foreign.Marshal.Alloc (free)
import GHC.Base (when)
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 (Word32)
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.NamedType ((:::))
import Vulkan.Core10.AllocationCallbacks (AllocationCallbacks)
import Vulkan.Core10.FundamentalTypes (Bool32)
import Vulkan.Core10.Handles (Device)
import Vulkan.Core10.Handles (Device(..))
import Vulkan.Core10.Handles (Device(Device))
import Vulkan.Dynamic (DeviceCmds(pVkCreatePrivateDataSlot))
import Vulkan.Dynamic (DeviceCmds(pVkDestroyPrivateDataSlot))
import Vulkan.Dynamic (DeviceCmds(pVkGetPrivateData))
import Vulkan.Dynamic (DeviceCmds(pVkSetPrivateData))
import Vulkan.Core10.Handles (Device_T)
import Vulkan.Core10.Enums.ObjectType (ObjectType)
import Vulkan.Core10.Enums.ObjectType (ObjectType(..))
import Vulkan.Core13.Handles (PrivateDataSlot)
import Vulkan.Core13.Handles (PrivateDataSlot(..))
import Vulkan.Core13.Enums.PrivateDataSlotCreateFlags (PrivateDataSlotCreateFlags)
import Vulkan.Core10.Enums.Result (Result)
import Vulkan.Core10.Enums.Result (Result(..))
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Exception (VulkanException(..))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_DEVICE_PRIVATE_DATA_CREATE_INFO))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_PRIVATE_DATA_FEATURES))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PRIVATE_DATA_SLOT_CREATE_INFO))
import Vulkan.Core10.Enums.Result (Result(SUCCESS))
import Vulkan.Core10.Enums.ObjectType (ObjectType(..))
import Vulkan.Core13.Handles (PrivateDataSlot(..))
import Vulkan.Core13.Enums.PrivateDataSlotCreateFlags (PrivateDataSlotCreateFlags(..))
import Vulkan.Core10.Enums.StructureType (StructureType(..))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkCreatePrivateDataSlot
:: FunPtr (Ptr Device_T -> Ptr PrivateDataSlotCreateInfo -> Ptr AllocationCallbacks -> Ptr PrivateDataSlot -> IO Result) -> Ptr Device_T -> Ptr PrivateDataSlotCreateInfo -> Ptr AllocationCallbacks -> Ptr PrivateDataSlot -> IO Result
createPrivateDataSlot :: forall io
. (MonadIO io)
=>
Device
->
PrivateDataSlotCreateInfo
->
("allocator" ::: Maybe AllocationCallbacks)
-> io (PrivateDataSlot)
createPrivateDataSlot :: forall (io :: * -> *).
MonadIO io =>
Device
-> PrivateDataSlotCreateInfo
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io PrivateDataSlot
createPrivateDataSlot Device
device PrivateDataSlotCreateInfo
createInfo "allocator" ::: Maybe AllocationCallbacks
allocator = 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 vkCreatePrivateDataSlotPtr :: FunPtr
(Ptr Device_T
-> ("pCreateInfo" ::: Ptr PrivateDataSlotCreateInfo)
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pPrivateDataSlot" ::: Ptr PrivateDataSlot)
-> IO Result)
vkCreatePrivateDataSlotPtr = DeviceCmds
-> FunPtr
(Ptr Device_T
-> ("pCreateInfo" ::: Ptr PrivateDataSlotCreateInfo)
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pPrivateDataSlot" ::: Ptr PrivateDataSlot)
-> IO Result)
pVkCreatePrivateDataSlot (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
-> ("pCreateInfo" ::: Ptr PrivateDataSlotCreateInfo)
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pPrivateDataSlot" ::: Ptr PrivateDataSlot)
-> IO Result)
vkCreatePrivateDataSlotPtr 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 vkCreatePrivateDataSlot is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
let vkCreatePrivateDataSlot' :: Ptr Device_T
-> ("pCreateInfo" ::: Ptr PrivateDataSlotCreateInfo)
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pPrivateDataSlot" ::: Ptr PrivateDataSlot)
-> IO Result
vkCreatePrivateDataSlot' = FunPtr
(Ptr Device_T
-> ("pCreateInfo" ::: Ptr PrivateDataSlotCreateInfo)
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pPrivateDataSlot" ::: Ptr PrivateDataSlot)
-> IO Result)
-> Ptr Device_T
-> ("pCreateInfo" ::: Ptr PrivateDataSlotCreateInfo)
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pPrivateDataSlot" ::: Ptr PrivateDataSlot)
-> IO Result
mkVkCreatePrivateDataSlot FunPtr
(Ptr Device_T
-> ("pCreateInfo" ::: Ptr PrivateDataSlotCreateInfo)
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pPrivateDataSlot" ::: Ptr PrivateDataSlot)
-> IO Result)
vkCreatePrivateDataSlotPtr
"pCreateInfo" ::: Ptr PrivateDataSlotCreateInfo
pCreateInfo <- 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 (PrivateDataSlotCreateInfo
createInfo)
"pAllocator" ::: Ptr AllocationCallbacks
pAllocator <- case ("allocator" ::: Maybe AllocationCallbacks
allocator) of
"allocator" ::: Maybe AllocationCallbacks
Nothing -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. Ptr a
nullPtr
Just AllocationCallbacks
j -> 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 (AllocationCallbacks
j)
"pPrivateDataSlot" ::: Ptr PrivateDataSlot
pPPrivateDataSlot <- 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 c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (forall a. Int -> IO (Ptr a)
callocBytes @PrivateDataSlot Int
8) forall a. Ptr a -> IO ()
free
Result
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
"vkCreatePrivateDataSlot" (Ptr Device_T
-> ("pCreateInfo" ::: Ptr PrivateDataSlotCreateInfo)
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pPrivateDataSlot" ::: Ptr PrivateDataSlot)
-> IO Result
vkCreatePrivateDataSlot'
(Device -> Ptr Device_T
deviceHandle (Device
device))
"pCreateInfo" ::: Ptr PrivateDataSlotCreateInfo
pCreateInfo
"pAllocator" ::: Ptr AllocationCallbacks
pAllocator
("pPrivateDataSlot" ::: Ptr PrivateDataSlot
pPPrivateDataSlot))
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 ()
when (Result
r forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r))
PrivateDataSlot
pPrivateDataSlot <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> IO a
peek @PrivateDataSlot "pPrivateDataSlot" ::: Ptr PrivateDataSlot
pPPrivateDataSlot
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ (PrivateDataSlot
pPrivateDataSlot)
withPrivateDataSlot :: forall io r . MonadIO io => Device -> PrivateDataSlotCreateInfo -> Maybe AllocationCallbacks -> (io PrivateDataSlot -> (PrivateDataSlot -> io ()) -> r) -> r
withPrivateDataSlot :: forall (io :: * -> *) r.
MonadIO io =>
Device
-> PrivateDataSlotCreateInfo
-> ("allocator" ::: Maybe AllocationCallbacks)
-> (io PrivateDataSlot -> (PrivateDataSlot -> io ()) -> r)
-> r
withPrivateDataSlot Device
device PrivateDataSlotCreateInfo
pCreateInfo "allocator" ::: Maybe AllocationCallbacks
pAllocator io PrivateDataSlot -> (PrivateDataSlot -> io ()) -> r
b =
io PrivateDataSlot -> (PrivateDataSlot -> io ()) -> r
b (forall (io :: * -> *).
MonadIO io =>
Device
-> PrivateDataSlotCreateInfo
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io PrivateDataSlot
createPrivateDataSlot Device
device PrivateDataSlotCreateInfo
pCreateInfo "allocator" ::: Maybe AllocationCallbacks
pAllocator)
(\(PrivateDataSlot
o0) -> forall (io :: * -> *).
MonadIO io =>
Device
-> PrivateDataSlot
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io ()
destroyPrivateDataSlot Device
device PrivateDataSlot
o0 "allocator" ::: Maybe AllocationCallbacks
pAllocator)
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkDestroyPrivateDataSlot
:: FunPtr (Ptr Device_T -> PrivateDataSlot -> Ptr AllocationCallbacks -> IO ()) -> Ptr Device_T -> PrivateDataSlot -> Ptr AllocationCallbacks -> IO ()
destroyPrivateDataSlot :: forall io
. (MonadIO io)
=>
Device
->
PrivateDataSlot
->
("allocator" ::: Maybe AllocationCallbacks)
-> io ()
destroyPrivateDataSlot :: forall (io :: * -> *).
MonadIO io =>
Device
-> PrivateDataSlot
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io ()
destroyPrivateDataSlot Device
device
PrivateDataSlot
privateDataSlot
"allocator" ::: Maybe AllocationCallbacks
allocator = 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 vkDestroyPrivateDataSlotPtr :: FunPtr
(Ptr Device_T
-> PrivateDataSlot
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ())
vkDestroyPrivateDataSlotPtr = DeviceCmds
-> FunPtr
(Ptr Device_T
-> PrivateDataSlot
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ())
pVkDestroyPrivateDataSlot (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
-> PrivateDataSlot
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ())
vkDestroyPrivateDataSlotPtr 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 vkDestroyPrivateDataSlot is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
let vkDestroyPrivateDataSlot' :: Ptr Device_T
-> PrivateDataSlot
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ()
vkDestroyPrivateDataSlot' = FunPtr
(Ptr Device_T
-> PrivateDataSlot
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ())
-> Ptr Device_T
-> PrivateDataSlot
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ()
mkVkDestroyPrivateDataSlot FunPtr
(Ptr Device_T
-> PrivateDataSlot
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ())
vkDestroyPrivateDataSlotPtr
"pAllocator" ::: Ptr AllocationCallbacks
pAllocator <- case ("allocator" ::: Maybe AllocationCallbacks
allocator) of
"allocator" ::: Maybe AllocationCallbacks
Nothing -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. Ptr a
nullPtr
Just AllocationCallbacks
j -> 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 (AllocationCallbacks
j)
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
"vkDestroyPrivateDataSlot" (Ptr Device_T
-> PrivateDataSlot
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ()
vkDestroyPrivateDataSlot'
(Device -> Ptr Device_T
deviceHandle (Device
device))
(PrivateDataSlot
privateDataSlot)
"pAllocator" ::: Ptr AllocationCallbacks
pAllocator)
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ ()
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkSetPrivateData
:: FunPtr (Ptr Device_T -> ObjectType -> Word64 -> PrivateDataSlot -> Word64 -> IO Result) -> Ptr Device_T -> ObjectType -> Word64 -> PrivateDataSlot -> Word64 -> IO Result
setPrivateData :: forall io
. (MonadIO io)
=>
Device
->
ObjectType
->
("objectHandle" ::: Word64)
->
PrivateDataSlot
->
("data" ::: Word64)
-> io ()
setPrivateData :: forall (io :: * -> *).
MonadIO io =>
Device
-> ObjectType
-> ("objectHandle" ::: Word64)
-> PrivateDataSlot
-> ("objectHandle" ::: Word64)
-> io ()
setPrivateData Device
device
ObjectType
objectType
"objectHandle" ::: Word64
objectHandle
PrivateDataSlot
privateDataSlot
"objectHandle" ::: Word64
data' = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
let vkSetPrivateDataPtr :: FunPtr
(Ptr Device_T
-> ObjectType
-> ("objectHandle" ::: Word64)
-> PrivateDataSlot
-> ("objectHandle" ::: Word64)
-> IO Result)
vkSetPrivateDataPtr = DeviceCmds
-> FunPtr
(Ptr Device_T
-> ObjectType
-> ("objectHandle" ::: Word64)
-> PrivateDataSlot
-> ("objectHandle" ::: Word64)
-> IO Result)
pVkSetPrivateData (case Device
device of Device{DeviceCmds
deviceCmds :: DeviceCmds
$sel:deviceCmds:Device :: Device -> DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
(Ptr Device_T
-> ObjectType
-> ("objectHandle" ::: Word64)
-> PrivateDataSlot
-> ("objectHandle" ::: Word64)
-> IO Result)
vkSetPrivateDataPtr 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 vkSetPrivateData is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
let vkSetPrivateData' :: Ptr Device_T
-> ObjectType
-> ("objectHandle" ::: Word64)
-> PrivateDataSlot
-> ("objectHandle" ::: Word64)
-> IO Result
vkSetPrivateData' = FunPtr
(Ptr Device_T
-> ObjectType
-> ("objectHandle" ::: Word64)
-> PrivateDataSlot
-> ("objectHandle" ::: Word64)
-> IO Result)
-> Ptr Device_T
-> ObjectType
-> ("objectHandle" ::: Word64)
-> PrivateDataSlot
-> ("objectHandle" ::: Word64)
-> IO Result
mkVkSetPrivateData FunPtr
(Ptr Device_T
-> ObjectType
-> ("objectHandle" ::: Word64)
-> PrivateDataSlot
-> ("objectHandle" ::: Word64)
-> IO Result)
vkSetPrivateDataPtr
Result
r <- forall a. String -> IO a -> IO a
traceAroundEvent String
"vkSetPrivateData" (Ptr Device_T
-> ObjectType
-> ("objectHandle" ::: Word64)
-> PrivateDataSlot
-> ("objectHandle" ::: Word64)
-> IO Result
vkSetPrivateData'
(Device -> Ptr Device_T
deviceHandle (Device
device))
(ObjectType
objectType)
("objectHandle" ::: Word64
objectHandle)
(PrivateDataSlot
privateDataSlot)
("objectHandle" ::: Word64
data'))
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkGetPrivateData
:: FunPtr (Ptr Device_T -> ObjectType -> Word64 -> PrivateDataSlot -> Ptr Word64 -> IO ()) -> Ptr Device_T -> ObjectType -> Word64 -> PrivateDataSlot -> Ptr Word64 -> IO ()
getPrivateData :: forall io
. (MonadIO io)
=>
Device
->
ObjectType
->
("objectHandle" ::: Word64)
->
PrivateDataSlot
-> io (("data" ::: Word64))
getPrivateData :: forall (io :: * -> *).
MonadIO io =>
Device
-> ObjectType
-> ("objectHandle" ::: Word64)
-> PrivateDataSlot
-> io ("objectHandle" ::: Word64)
getPrivateData Device
device
ObjectType
objectType
"objectHandle" ::: Word64
objectHandle
PrivateDataSlot
privateDataSlot = 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 vkGetPrivateDataPtr :: FunPtr
(Ptr Device_T
-> ObjectType
-> ("objectHandle" ::: Word64)
-> PrivateDataSlot
-> ("pData" ::: Ptr ("objectHandle" ::: Word64))
-> IO ())
vkGetPrivateDataPtr = DeviceCmds
-> FunPtr
(Ptr Device_T
-> ObjectType
-> ("objectHandle" ::: Word64)
-> PrivateDataSlot
-> ("pData" ::: Ptr ("objectHandle" ::: Word64))
-> IO ())
pVkGetPrivateData (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
-> ObjectType
-> ("objectHandle" ::: Word64)
-> PrivateDataSlot
-> ("pData" ::: Ptr ("objectHandle" ::: Word64))
-> IO ())
vkGetPrivateDataPtr 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 vkGetPrivateData is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
let vkGetPrivateData' :: Ptr Device_T
-> ObjectType
-> ("objectHandle" ::: Word64)
-> PrivateDataSlot
-> ("pData" ::: Ptr ("objectHandle" ::: Word64))
-> IO ()
vkGetPrivateData' = FunPtr
(Ptr Device_T
-> ObjectType
-> ("objectHandle" ::: Word64)
-> PrivateDataSlot
-> ("pData" ::: Ptr ("objectHandle" ::: Word64))
-> IO ())
-> Ptr Device_T
-> ObjectType
-> ("objectHandle" ::: Word64)
-> PrivateDataSlot
-> ("pData" ::: Ptr ("objectHandle" ::: Word64))
-> IO ()
mkVkGetPrivateData FunPtr
(Ptr Device_T
-> ObjectType
-> ("objectHandle" ::: Word64)
-> PrivateDataSlot
-> ("pData" ::: Ptr ("objectHandle" ::: Word64))
-> IO ())
vkGetPrivateDataPtr
"pData" ::: Ptr ("objectHandle" ::: Word64)
pPData <- 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 c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (forall a. Int -> IO (Ptr a)
callocBytes @Word64 Int
8) forall a. Ptr a -> IO ()
free
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
"vkGetPrivateData" (Ptr Device_T
-> ObjectType
-> ("objectHandle" ::: Word64)
-> PrivateDataSlot
-> ("pData" ::: Ptr ("objectHandle" ::: Word64))
-> IO ()
vkGetPrivateData'
(Device -> Ptr Device_T
deviceHandle (Device
device))
(ObjectType
objectType)
("objectHandle" ::: Word64
objectHandle)
(PrivateDataSlot
privateDataSlot)
("pData" ::: Ptr ("objectHandle" ::: Word64)
pPData))
"objectHandle" ::: Word64
pData <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> IO a
peek @Word64 "pData" ::: Ptr ("objectHandle" ::: Word64)
pPData
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ ("objectHandle" ::: Word64
pData)
data DevicePrivateDataCreateInfo = DevicePrivateDataCreateInfo
{
DevicePrivateDataCreateInfo -> Word32
privateDataSlotRequestCount :: Word32 }
deriving (Typeable, DevicePrivateDataCreateInfo -> DevicePrivateDataCreateInfo -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DevicePrivateDataCreateInfo -> DevicePrivateDataCreateInfo -> Bool
$c/= :: DevicePrivateDataCreateInfo -> DevicePrivateDataCreateInfo -> Bool
== :: DevicePrivateDataCreateInfo -> DevicePrivateDataCreateInfo -> Bool
$c== :: DevicePrivateDataCreateInfo -> DevicePrivateDataCreateInfo -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (DevicePrivateDataCreateInfo)
#endif
deriving instance Show DevicePrivateDataCreateInfo
instance ToCStruct DevicePrivateDataCreateInfo where
withCStruct :: forall b.
DevicePrivateDataCreateInfo
-> (Ptr DevicePrivateDataCreateInfo -> IO b) -> IO b
withCStruct DevicePrivateDataCreateInfo
x Ptr DevicePrivateDataCreateInfo -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr DevicePrivateDataCreateInfo
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr DevicePrivateDataCreateInfo
p DevicePrivateDataCreateInfo
x (Ptr DevicePrivateDataCreateInfo -> IO b
f Ptr DevicePrivateDataCreateInfo
p)
pokeCStruct :: forall b.
Ptr DevicePrivateDataCreateInfo
-> DevicePrivateDataCreateInfo -> IO b -> IO b
pokeCStruct Ptr DevicePrivateDataCreateInfo
p DevicePrivateDataCreateInfo{Word32
privateDataSlotRequestCount :: Word32
$sel:privateDataSlotRequestCount:DevicePrivateDataCreateInfo :: DevicePrivateDataCreateInfo -> Word32
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DevicePrivateDataCreateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DEVICE_PRIVATE_DATA_CREATE_INFO)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DevicePrivateDataCreateInfo
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 DevicePrivateDataCreateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32)) (Word32
privateDataSlotRequestCount)
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b. Ptr DevicePrivateDataCreateInfo -> IO b -> IO b
pokeZeroCStruct Ptr DevicePrivateDataCreateInfo
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DevicePrivateDataCreateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DEVICE_PRIVATE_DATA_CREATE_INFO)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DevicePrivateDataCreateInfo
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 DevicePrivateDataCreateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32)) (forall a. Zero a => a
zero)
IO b
f
instance FromCStruct DevicePrivateDataCreateInfo where
peekCStruct :: Ptr DevicePrivateDataCreateInfo -> IO DevicePrivateDataCreateInfo
peekCStruct Ptr DevicePrivateDataCreateInfo
p = do
Word32
privateDataSlotRequestCount <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr DevicePrivateDataCreateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Word32 -> DevicePrivateDataCreateInfo
DevicePrivateDataCreateInfo
Word32
privateDataSlotRequestCount
instance Storable DevicePrivateDataCreateInfo where
sizeOf :: DevicePrivateDataCreateInfo -> Int
sizeOf ~DevicePrivateDataCreateInfo
_ = Int
24
alignment :: DevicePrivateDataCreateInfo -> Int
alignment ~DevicePrivateDataCreateInfo
_ = Int
8
peek :: Ptr DevicePrivateDataCreateInfo -> IO DevicePrivateDataCreateInfo
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr DevicePrivateDataCreateInfo
-> DevicePrivateDataCreateInfo -> IO ()
poke Ptr DevicePrivateDataCreateInfo
ptr DevicePrivateDataCreateInfo
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr DevicePrivateDataCreateInfo
ptr DevicePrivateDataCreateInfo
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero DevicePrivateDataCreateInfo where
zero :: DevicePrivateDataCreateInfo
zero = Word32 -> DevicePrivateDataCreateInfo
DevicePrivateDataCreateInfo
forall a. Zero a => a
zero
data PrivateDataSlotCreateInfo = PrivateDataSlotCreateInfo
{
PrivateDataSlotCreateInfo -> PrivateDataSlotCreateFlags
flags :: PrivateDataSlotCreateFlags }
deriving (Typeable, PrivateDataSlotCreateInfo -> PrivateDataSlotCreateInfo -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PrivateDataSlotCreateInfo -> PrivateDataSlotCreateInfo -> Bool
$c/= :: PrivateDataSlotCreateInfo -> PrivateDataSlotCreateInfo -> Bool
== :: PrivateDataSlotCreateInfo -> PrivateDataSlotCreateInfo -> Bool
$c== :: PrivateDataSlotCreateInfo -> PrivateDataSlotCreateInfo -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PrivateDataSlotCreateInfo)
#endif
deriving instance Show PrivateDataSlotCreateInfo
instance ToCStruct PrivateDataSlotCreateInfo where
withCStruct :: forall b.
PrivateDataSlotCreateInfo
-> (("pCreateInfo" ::: Ptr PrivateDataSlotCreateInfo) -> IO b)
-> IO b
withCStruct PrivateDataSlotCreateInfo
x ("pCreateInfo" ::: Ptr PrivateDataSlotCreateInfo) -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \"pCreateInfo" ::: Ptr PrivateDataSlotCreateInfo
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pCreateInfo" ::: Ptr PrivateDataSlotCreateInfo
p PrivateDataSlotCreateInfo
x (("pCreateInfo" ::: Ptr PrivateDataSlotCreateInfo) -> IO b
f "pCreateInfo" ::: Ptr PrivateDataSlotCreateInfo
p)
pokeCStruct :: forall b.
("pCreateInfo" ::: Ptr PrivateDataSlotCreateInfo)
-> PrivateDataSlotCreateInfo -> IO b -> IO b
pokeCStruct "pCreateInfo" ::: Ptr PrivateDataSlotCreateInfo
p PrivateDataSlotCreateInfo{PrivateDataSlotCreateFlags
flags :: PrivateDataSlotCreateFlags
$sel:flags:PrivateDataSlotCreateInfo :: PrivateDataSlotCreateInfo -> PrivateDataSlotCreateFlags
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr PrivateDataSlotCreateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PRIVATE_DATA_SLOT_CREATE_INFO)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr PrivateDataSlotCreateInfo
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 (("pCreateInfo" ::: Ptr PrivateDataSlotCreateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr PrivateDataSlotCreateFlags)) (PrivateDataSlotCreateFlags
flags)
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
("pCreateInfo" ::: Ptr PrivateDataSlotCreateInfo) -> IO b -> IO b
pokeZeroCStruct "pCreateInfo" ::: Ptr PrivateDataSlotCreateInfo
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr PrivateDataSlotCreateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PRIVATE_DATA_SLOT_CREATE_INFO)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr PrivateDataSlotCreateInfo
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 (("pCreateInfo" ::: Ptr PrivateDataSlotCreateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr PrivateDataSlotCreateFlags)) (forall a. Zero a => a
zero)
IO b
f
instance FromCStruct PrivateDataSlotCreateInfo where
peekCStruct :: ("pCreateInfo" ::: Ptr PrivateDataSlotCreateInfo)
-> IO PrivateDataSlotCreateInfo
peekCStruct "pCreateInfo" ::: Ptr PrivateDataSlotCreateInfo
p = do
PrivateDataSlotCreateFlags
flags <- forall a. Storable a => Ptr a -> IO a
peek @PrivateDataSlotCreateFlags (("pCreateInfo" ::: Ptr PrivateDataSlotCreateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr PrivateDataSlotCreateFlags))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ PrivateDataSlotCreateFlags -> PrivateDataSlotCreateInfo
PrivateDataSlotCreateInfo
PrivateDataSlotCreateFlags
flags
instance Storable PrivateDataSlotCreateInfo where
sizeOf :: PrivateDataSlotCreateInfo -> Int
sizeOf ~PrivateDataSlotCreateInfo
_ = Int
24
alignment :: PrivateDataSlotCreateInfo -> Int
alignment ~PrivateDataSlotCreateInfo
_ = Int
8
peek :: ("pCreateInfo" ::: Ptr PrivateDataSlotCreateInfo)
-> IO PrivateDataSlotCreateInfo
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: ("pCreateInfo" ::: Ptr PrivateDataSlotCreateInfo)
-> PrivateDataSlotCreateInfo -> IO ()
poke "pCreateInfo" ::: Ptr PrivateDataSlotCreateInfo
ptr PrivateDataSlotCreateInfo
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pCreateInfo" ::: Ptr PrivateDataSlotCreateInfo
ptr PrivateDataSlotCreateInfo
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PrivateDataSlotCreateInfo where
zero :: PrivateDataSlotCreateInfo
zero = PrivateDataSlotCreateFlags -> PrivateDataSlotCreateInfo
PrivateDataSlotCreateInfo
forall a. Zero a => a
zero
data PhysicalDevicePrivateDataFeatures = PhysicalDevicePrivateDataFeatures
{
PhysicalDevicePrivateDataFeatures -> Bool
privateData :: Bool }
deriving (Typeable, PhysicalDevicePrivateDataFeatures
-> PhysicalDevicePrivateDataFeatures -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDevicePrivateDataFeatures
-> PhysicalDevicePrivateDataFeatures -> Bool
$c/= :: PhysicalDevicePrivateDataFeatures
-> PhysicalDevicePrivateDataFeatures -> Bool
== :: PhysicalDevicePrivateDataFeatures
-> PhysicalDevicePrivateDataFeatures -> Bool
$c== :: PhysicalDevicePrivateDataFeatures
-> PhysicalDevicePrivateDataFeatures -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDevicePrivateDataFeatures)
#endif
deriving instance Show PhysicalDevicePrivateDataFeatures
instance ToCStruct PhysicalDevicePrivateDataFeatures where
withCStruct :: forall b.
PhysicalDevicePrivateDataFeatures
-> (Ptr PhysicalDevicePrivateDataFeatures -> IO b) -> IO b
withCStruct PhysicalDevicePrivateDataFeatures
x Ptr PhysicalDevicePrivateDataFeatures -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDevicePrivateDataFeatures
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDevicePrivateDataFeatures
p PhysicalDevicePrivateDataFeatures
x (Ptr PhysicalDevicePrivateDataFeatures -> IO b
f Ptr PhysicalDevicePrivateDataFeatures
p)
pokeCStruct :: forall b.
Ptr PhysicalDevicePrivateDataFeatures
-> PhysicalDevicePrivateDataFeatures -> IO b -> IO b
pokeCStruct Ptr PhysicalDevicePrivateDataFeatures
p PhysicalDevicePrivateDataFeatures{Bool
privateData :: Bool
$sel:privateData:PhysicalDevicePrivateDataFeatures :: PhysicalDevicePrivateDataFeatures -> Bool
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePrivateDataFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_PRIVATE_DATA_FEATURES)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePrivateDataFeatures
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 PhysicalDevicePrivateDataFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
privateData))
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b. Ptr PhysicalDevicePrivateDataFeatures -> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDevicePrivateDataFeatures
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePrivateDataFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_PRIVATE_DATA_FEATURES)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevicePrivateDataFeatures
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 PhysicalDevicePrivateDataFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
IO b
f
instance FromCStruct PhysicalDevicePrivateDataFeatures where
peekCStruct :: Ptr PhysicalDevicePrivateDataFeatures
-> IO PhysicalDevicePrivateDataFeatures
peekCStruct Ptr PhysicalDevicePrivateDataFeatures
p = do
Bool32
privateData <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDevicePrivateDataFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Bool -> PhysicalDevicePrivateDataFeatures
PhysicalDevicePrivateDataFeatures
(Bool32 -> Bool
bool32ToBool Bool32
privateData)
instance Storable PhysicalDevicePrivateDataFeatures where
sizeOf :: PhysicalDevicePrivateDataFeatures -> Int
sizeOf ~PhysicalDevicePrivateDataFeatures
_ = Int
24
alignment :: PhysicalDevicePrivateDataFeatures -> Int
alignment ~PhysicalDevicePrivateDataFeatures
_ = Int
8
peek :: Ptr PhysicalDevicePrivateDataFeatures
-> IO PhysicalDevicePrivateDataFeatures
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr PhysicalDevicePrivateDataFeatures
-> PhysicalDevicePrivateDataFeatures -> IO ()
poke Ptr PhysicalDevicePrivateDataFeatures
ptr PhysicalDevicePrivateDataFeatures
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDevicePrivateDataFeatures
ptr PhysicalDevicePrivateDataFeatures
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PhysicalDevicePrivateDataFeatures where
zero :: PhysicalDevicePrivateDataFeatures
zero = Bool -> PhysicalDevicePrivateDataFeatures
PhysicalDevicePrivateDataFeatures
forall a. Zero a => a
zero