{-# language CPP #-}
module Vulkan.Core10.CommandBuffer ( allocateCommandBuffers
, withCommandBuffers
, freeCommandBuffers
, beginCommandBuffer
, useCommandBuffer
, endCommandBuffer
, resetCommandBuffer
, CommandBufferAllocateInfo(..)
, CommandBufferInheritanceInfo(..)
, CommandBufferBeginInfo(..)
, CommandBuffer(..)
, CommandBufferLevel(..)
, QueryControlFlagBits(..)
, QueryControlFlags
, CommandBufferUsageFlagBits(..)
, CommandBufferUsageFlags
, CommandBufferResetFlagBits(..)
, CommandBufferResetFlags
) where
import Vulkan.Internal.Utils (traceAroundEvent)
import Control.Exception.Base (bracket)
import Control.Monad (unless)
import Control.Monad.IO.Class (liftIO)
import Data.Typeable (eqT)
import Foreign.Marshal.Alloc (allocaBytes)
import Foreign.Marshal.Alloc (callocBytes)
import Foreign.Marshal.Alloc (free)
import Foreign.Marshal.Utils (maybePeek)
import GHC.Base (when)
import GHC.IO (throwIO)
import GHC.Ptr (castPtr)
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 Data.Vector (generateM)
import qualified Data.Vector (imapM_)
import qualified Data.Vector (length)
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.Type.Equality ((:~:)(Refl))
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.Kind (Type)
import Control.Monad.Trans.Cont (ContT(..))
import Data.Vector (Vector)
import Vulkan.CStruct.Utils (advancePtrBytes)
import Vulkan.Core10.FundamentalTypes (bool32ToBool)
import Vulkan.Core10.FundamentalTypes (boolToBool32)
import Vulkan.CStruct.Extends (forgetExtensions)
import Vulkan.CStruct.Extends (peekSomeCStruct)
import Vulkan.CStruct.Extends (withSomeCStruct)
import Vulkan.NamedType ((:::))
import {-# SOURCE #-} Vulkan.Extensions.VK_KHR_dynamic_rendering (AttachmentSampleCountInfoAMD)
import Vulkan.Core10.FundamentalTypes (Bool32)
import Vulkan.CStruct.Extends (Chain)
import Vulkan.Core10.Handles (CommandBuffer)
import Vulkan.Core10.Handles (CommandBuffer(..))
import Vulkan.Core10.Handles (CommandBuffer(CommandBuffer))
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_conditional_rendering (CommandBufferInheritanceConditionalRenderingInfoEXT)
import {-# SOURCE #-} Vulkan.Extensions.VK_QCOM_render_pass_transform (CommandBufferInheritanceRenderPassTransformInfoQCOM)
import {-# SOURCE #-} Vulkan.Core13.Promoted_From_VK_KHR_dynamic_rendering (CommandBufferInheritanceRenderingInfo)
import {-# SOURCE #-} Vulkan.Extensions.VK_NV_inherited_viewport_scissor (CommandBufferInheritanceViewportScissorInfoNV)
import Vulkan.Core10.Enums.CommandBufferLevel (CommandBufferLevel)
import Vulkan.Core10.Enums.CommandBufferResetFlagBits (CommandBufferResetFlagBits(..))
import Vulkan.Core10.Enums.CommandBufferResetFlagBits (CommandBufferResetFlags)
import Vulkan.Core10.Enums.CommandBufferUsageFlagBits (CommandBufferUsageFlags)
import Vulkan.Core10.Handles (CommandBuffer_T)
import Vulkan.Core10.Handles (CommandPool)
import Vulkan.Core10.Handles (CommandPool(..))
import Vulkan.Core10.Handles (Device)
import Vulkan.Core10.Handles (Device(..))
import Vulkan.Core10.Handles (Device(Device))
import Vulkan.Dynamic (DeviceCmds(pVkAllocateCommandBuffers))
import Vulkan.Dynamic (DeviceCmds(pVkBeginCommandBuffer))
import Vulkan.Dynamic (DeviceCmds(pVkEndCommandBuffer))
import Vulkan.Dynamic (DeviceCmds(pVkFreeCommandBuffers))
import Vulkan.Dynamic (DeviceCmds(pVkResetCommandBuffer))
import {-# SOURCE #-} Vulkan.Core11.Promoted_From_VK_KHR_device_group (DeviceGroupCommandBufferBeginInfo)
import Vulkan.Core10.Handles (Device_T)
import Vulkan.CStruct.Extends (Extends)
import Vulkan.CStruct.Extends (Extendss)
import Vulkan.CStruct.Extends (Extensible(..))
import {-# SOURCE #-} Vulkan.Extensions.VK_ANDROID_external_memory_android_hardware_buffer (ExternalFormatANDROID)
import Vulkan.Core10.Handles (Framebuffer)
import {-# SOURCE #-} Vulkan.Extensions.VK_KHR_dynamic_rendering (MultiviewPerViewAttributesInfoNVX)
import Vulkan.CStruct.Extends (PeekChain)
import Vulkan.CStruct.Extends (PeekChain(..))
import Vulkan.CStruct.Extends (PokeChain)
import Vulkan.CStruct.Extends (PokeChain(..))
import Vulkan.Core10.Enums.QueryControlFlagBits (QueryControlFlags)
import Vulkan.Core10.Enums.QueryPipelineStatisticFlagBits (QueryPipelineStatisticFlags)
import Vulkan.Core10.Handles (RenderPass)
import Vulkan.Core10.Enums.Result (Result)
import Vulkan.Core10.Enums.Result (Result(..))
import Vulkan.CStruct.Extends (SomeStruct)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Exception (VulkanException(..))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_COMMAND_BUFFER_ALLOCATE_INFO))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_COMMAND_BUFFER_BEGIN_INFO))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_COMMAND_BUFFER_INHERITANCE_INFO))
import Vulkan.Core10.Enums.Result (Result(SUCCESS))
import Vulkan.Core10.Handles (CommandBuffer(..))
import Vulkan.Core10.Enums.CommandBufferLevel (CommandBufferLevel(..))
import Vulkan.Core10.Enums.CommandBufferResetFlagBits (CommandBufferResetFlagBits(..))
import Vulkan.Core10.Enums.CommandBufferResetFlagBits (CommandBufferResetFlags)
import Vulkan.Core10.Enums.CommandBufferUsageFlagBits (CommandBufferUsageFlagBits(..))
import Vulkan.Core10.Enums.CommandBufferUsageFlagBits (CommandBufferUsageFlags)
import Vulkan.Core10.Enums.QueryControlFlagBits (QueryControlFlagBits(..))
import Vulkan.Core10.Enums.QueryControlFlagBits (QueryControlFlags)
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkAllocateCommandBuffers
:: FunPtr (Ptr Device_T -> Ptr CommandBufferAllocateInfo -> Ptr (Ptr CommandBuffer_T) -> IO Result) -> Ptr Device_T -> Ptr CommandBufferAllocateInfo -> Ptr (Ptr CommandBuffer_T) -> IO Result
allocateCommandBuffers :: forall io
. (MonadIO io)
=>
Device
->
CommandBufferAllocateInfo
-> io (("commandBuffers" ::: Vector CommandBuffer))
allocateCommandBuffers :: forall (io :: * -> *).
MonadIO io =>
Device
-> CommandBufferAllocateInfo
-> io ("commandBuffers" ::: Vector CommandBuffer)
allocateCommandBuffers Device
device CommandBufferAllocateInfo
allocateInfo = 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 cmds :: DeviceCmds
cmds = case Device
device of Device{DeviceCmds
$sel:deviceCmds:Device :: Device -> DeviceCmds
deviceCmds :: DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds
let vkAllocateCommandBuffersPtr :: FunPtr
(Ptr Device_T
-> ("pAllocateInfo" ::: Ptr CommandBufferAllocateInfo)
-> ("pCommandBuffers" ::: Ptr (Ptr CommandBuffer_T))
-> IO Result)
vkAllocateCommandBuffersPtr = DeviceCmds
-> FunPtr
(Ptr Device_T
-> ("pAllocateInfo" ::: Ptr CommandBufferAllocateInfo)
-> ("pCommandBuffers" ::: Ptr (Ptr CommandBuffer_T))
-> IO Result)
pVkAllocateCommandBuffers DeviceCmds
cmds
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
-> ("pAllocateInfo" ::: Ptr CommandBufferAllocateInfo)
-> ("pCommandBuffers" ::: Ptr (Ptr CommandBuffer_T))
-> IO Result)
vkAllocateCommandBuffersPtr 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 vkAllocateCommandBuffers is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
let vkAllocateCommandBuffers' :: Ptr Device_T
-> ("pAllocateInfo" ::: Ptr CommandBufferAllocateInfo)
-> ("pCommandBuffers" ::: Ptr (Ptr CommandBuffer_T))
-> IO Result
vkAllocateCommandBuffers' = FunPtr
(Ptr Device_T
-> ("pAllocateInfo" ::: Ptr CommandBufferAllocateInfo)
-> ("pCommandBuffers" ::: Ptr (Ptr CommandBuffer_T))
-> IO Result)
-> Ptr Device_T
-> ("pAllocateInfo" ::: Ptr CommandBufferAllocateInfo)
-> ("pCommandBuffers" ::: Ptr (Ptr CommandBuffer_T))
-> IO Result
mkVkAllocateCommandBuffers FunPtr
(Ptr Device_T
-> ("pAllocateInfo" ::: Ptr CommandBufferAllocateInfo)
-> ("pCommandBuffers" ::: Ptr (Ptr CommandBuffer_T))
-> IO Result)
vkAllocateCommandBuffersPtr
"pAllocateInfo" ::: Ptr CommandBufferAllocateInfo
pAllocateInfo <- 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 (CommandBufferAllocateInfo
allocateInfo)
"pCommandBuffers" ::: Ptr (Ptr CommandBuffer_T)
pPCommandBuffers <- 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 @(Ptr CommandBuffer_T) ((forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ CommandBufferAllocateInfo -> Word32
commandBufferCount ((CommandBufferAllocateInfo
allocateInfo) :: CommandBufferAllocateInfo)) forall a. Num a => a -> a -> a
* 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
"vkAllocateCommandBuffers" (Ptr Device_T
-> ("pAllocateInfo" ::: Ptr CommandBufferAllocateInfo)
-> ("pCommandBuffers" ::: Ptr (Ptr CommandBuffer_T))
-> IO Result
vkAllocateCommandBuffers'
(Device -> Ptr Device_T
deviceHandle (Device
device))
"pAllocateInfo" ::: Ptr CommandBufferAllocateInfo
pAllocateInfo
("pCommandBuffers" ::: Ptr (Ptr CommandBuffer_T)
pPCommandBuffers))
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))
"commandBuffers" ::: Vector CommandBuffer
pCommandBuffers <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ CommandBufferAllocateInfo -> Word32
commandBufferCount ((CommandBufferAllocateInfo
allocateInfo) :: CommandBufferAllocateInfo)) (\Int
i -> do
Ptr CommandBuffer_T
pCommandBuffersElem <- forall a. Storable a => Ptr a -> IO a
peek @(Ptr CommandBuffer_T) (("pCommandBuffers" ::: Ptr (Ptr CommandBuffer_T)
pPCommandBuffers forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (Int
8 forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (Ptr CommandBuffer_T)))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ (\Ptr CommandBuffer_T
h -> Ptr CommandBuffer_T -> DeviceCmds -> CommandBuffer
CommandBuffer Ptr CommandBuffer_T
h DeviceCmds
cmds ) Ptr CommandBuffer_T
pCommandBuffersElem)
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ ("commandBuffers" ::: Vector CommandBuffer
pCommandBuffers)
withCommandBuffers :: forall io r . MonadIO io => Device -> CommandBufferAllocateInfo -> (io (Vector CommandBuffer) -> (Vector CommandBuffer -> io ()) -> r) -> r
withCommandBuffers :: forall (io :: * -> *) r.
MonadIO io =>
Device
-> CommandBufferAllocateInfo
-> (io ("commandBuffers" ::: Vector CommandBuffer)
-> (("commandBuffers" ::: Vector CommandBuffer) -> io ()) -> r)
-> r
withCommandBuffers Device
device CommandBufferAllocateInfo
pAllocateInfo io ("commandBuffers" ::: Vector CommandBuffer)
-> (("commandBuffers" ::: Vector CommandBuffer) -> io ()) -> r
b =
io ("commandBuffers" ::: Vector CommandBuffer)
-> (("commandBuffers" ::: Vector CommandBuffer) -> io ()) -> r
b (forall (io :: * -> *).
MonadIO io =>
Device
-> CommandBufferAllocateInfo
-> io ("commandBuffers" ::: Vector CommandBuffer)
allocateCommandBuffers Device
device CommandBufferAllocateInfo
pAllocateInfo)
(\("commandBuffers" ::: Vector CommandBuffer
o0) -> forall (io :: * -> *).
MonadIO io =>
Device
-> CommandPool
-> ("commandBuffers" ::: Vector CommandBuffer)
-> io ()
freeCommandBuffers Device
device
(CommandBufferAllocateInfo -> CommandPool
commandPool (CommandBufferAllocateInfo
pAllocateInfo :: CommandBufferAllocateInfo))
"commandBuffers" ::: Vector CommandBuffer
o0)
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkFreeCommandBuffers
:: FunPtr (Ptr Device_T -> CommandPool -> Word32 -> Ptr (Ptr CommandBuffer_T) -> IO ()) -> Ptr Device_T -> CommandPool -> Word32 -> Ptr (Ptr CommandBuffer_T) -> IO ()
freeCommandBuffers :: forall io
. (MonadIO io)
=>
Device
->
CommandPool
->
("commandBuffers" ::: Vector CommandBuffer)
-> io ()
freeCommandBuffers :: forall (io :: * -> *).
MonadIO io =>
Device
-> CommandPool
-> ("commandBuffers" ::: Vector CommandBuffer)
-> io ()
freeCommandBuffers Device
device CommandPool
commandPool "commandBuffers" ::: Vector CommandBuffer
commandBuffers = 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 vkFreeCommandBuffersPtr :: FunPtr
(Ptr Device_T
-> CommandPool
-> Word32
-> ("pCommandBuffers" ::: Ptr (Ptr CommandBuffer_T))
-> IO ())
vkFreeCommandBuffersPtr = DeviceCmds
-> FunPtr
(Ptr Device_T
-> CommandPool
-> Word32
-> ("pCommandBuffers" ::: Ptr (Ptr CommandBuffer_T))
-> IO ())
pVkFreeCommandBuffers (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
-> CommandPool
-> Word32
-> ("pCommandBuffers" ::: Ptr (Ptr CommandBuffer_T))
-> IO ())
vkFreeCommandBuffersPtr 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 vkFreeCommandBuffers is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
let vkFreeCommandBuffers' :: Ptr Device_T
-> CommandPool
-> Word32
-> ("pCommandBuffers" ::: Ptr (Ptr CommandBuffer_T))
-> IO ()
vkFreeCommandBuffers' = FunPtr
(Ptr Device_T
-> CommandPool
-> Word32
-> ("pCommandBuffers" ::: Ptr (Ptr CommandBuffer_T))
-> IO ())
-> Ptr Device_T
-> CommandPool
-> Word32
-> ("pCommandBuffers" ::: Ptr (Ptr CommandBuffer_T))
-> IO ()
mkVkFreeCommandBuffers FunPtr
(Ptr Device_T
-> CommandPool
-> Word32
-> ("pCommandBuffers" ::: Ptr (Ptr CommandBuffer_T))
-> IO ())
vkFreeCommandBuffersPtr
"pCommandBuffers" ::: Ptr (Ptr CommandBuffer_T)
pPCommandBuffers <- 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. Int -> (Ptr a -> IO b) -> IO b
allocaBytes @(Ptr CommandBuffer_T) ((forall a. Vector a -> Int
Data.Vector.length ("commandBuffers" ::: Vector CommandBuffer
commandBuffers)) forall a. Num a => a -> a -> a
* Int
8)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\Int
i CommandBuffer
e -> forall a. Storable a => Ptr a -> a -> IO ()
poke ("pCommandBuffers" ::: Ptr (Ptr CommandBuffer_T)
pPCommandBuffers forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
8 forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (Ptr CommandBuffer_T)) (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
e))) ("commandBuffers" ::: Vector CommandBuffer
commandBuffers)
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
"vkFreeCommandBuffers" (Ptr Device_T
-> CommandPool
-> Word32
-> ("pCommandBuffers" ::: Ptr (Ptr CommandBuffer_T))
-> IO ()
vkFreeCommandBuffers'
(Device -> Ptr Device_T
deviceHandle (Device
device))
(CommandPool
commandPool)
((forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a. Vector a -> Int
Data.Vector.length forall a b. (a -> b) -> a -> b
$ ("commandBuffers" ::: Vector CommandBuffer
commandBuffers)) :: Word32))
("pCommandBuffers" ::: Ptr (Ptr CommandBuffer_T)
pPCommandBuffers))
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" mkVkBeginCommandBuffer
:: FunPtr (Ptr CommandBuffer_T -> Ptr (SomeStruct CommandBufferBeginInfo) -> IO Result) -> Ptr CommandBuffer_T -> Ptr (SomeStruct CommandBufferBeginInfo) -> IO Result
beginCommandBuffer :: forall a io
. ( Extendss CommandBufferBeginInfo a
, PokeChain a
, MonadIO io )
=>
CommandBuffer
->
(CommandBufferBeginInfo a)
-> io ()
beginCommandBuffer :: forall (a :: [*]) (io :: * -> *).
(Extendss CommandBufferBeginInfo a, PokeChain a, MonadIO io) =>
CommandBuffer -> CommandBufferBeginInfo a -> io ()
beginCommandBuffer CommandBuffer
commandBuffer CommandBufferBeginInfo a
beginInfo = 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 vkBeginCommandBufferPtr :: FunPtr
(Ptr CommandBuffer_T
-> ("pBeginInfo" ::: Ptr (SomeStruct CommandBufferBeginInfo))
-> IO Result)
vkBeginCommandBufferPtr = DeviceCmds
-> FunPtr
(Ptr CommandBuffer_T
-> ("pBeginInfo" ::: Ptr (SomeStruct CommandBufferBeginInfo))
-> IO Result)
pVkBeginCommandBuffer (case CommandBuffer
commandBuffer of CommandBuffer{DeviceCmds
$sel:deviceCmds:CommandBuffer :: CommandBuffer -> 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 CommandBuffer_T
-> ("pBeginInfo" ::: Ptr (SomeStruct CommandBufferBeginInfo))
-> IO Result)
vkBeginCommandBufferPtr 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 vkBeginCommandBuffer is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
let vkBeginCommandBuffer' :: Ptr CommandBuffer_T
-> ("pBeginInfo" ::: Ptr (SomeStruct CommandBufferBeginInfo))
-> IO Result
vkBeginCommandBuffer' = FunPtr
(Ptr CommandBuffer_T
-> ("pBeginInfo" ::: Ptr (SomeStruct CommandBufferBeginInfo))
-> IO Result)
-> Ptr CommandBuffer_T
-> ("pBeginInfo" ::: Ptr (SomeStruct CommandBufferBeginInfo))
-> IO Result
mkVkBeginCommandBuffer FunPtr
(Ptr CommandBuffer_T
-> ("pBeginInfo" ::: Ptr (SomeStruct CommandBufferBeginInfo))
-> IO Result)
vkBeginCommandBufferPtr
Ptr (CommandBufferBeginInfo a)
pBeginInfo <- 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 (CommandBufferBeginInfo a
beginInfo)
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
"vkBeginCommandBuffer" (Ptr CommandBuffer_T
-> ("pBeginInfo" ::: Ptr (SomeStruct CommandBufferBeginInfo))
-> IO Result
vkBeginCommandBuffer'
(CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer))
(forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions Ptr (CommandBufferBeginInfo a)
pBeginInfo))
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))
useCommandBuffer :: forall a io r . (Extendss CommandBufferBeginInfo a, PokeChain a, MonadIO io) => CommandBuffer -> CommandBufferBeginInfo a -> io r -> io r
useCommandBuffer :: forall (a :: [*]) (io :: * -> *) r.
(Extendss CommandBufferBeginInfo a, PokeChain a, MonadIO io) =>
CommandBuffer -> CommandBufferBeginInfo a -> io r -> io r
useCommandBuffer CommandBuffer
commandBuffer CommandBufferBeginInfo a
pBeginInfo io r
a =
(forall (a :: [*]) (io :: * -> *).
(Extendss CommandBufferBeginInfo a, PokeChain a, MonadIO io) =>
CommandBuffer -> CommandBufferBeginInfo a -> io ()
beginCommandBuffer CommandBuffer
commandBuffer
CommandBufferBeginInfo a
pBeginInfo) forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> io r
a forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* (forall (io :: * -> *). MonadIO io => CommandBuffer -> io ()
endCommandBuffer CommandBuffer
commandBuffer)
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkEndCommandBuffer
:: FunPtr (Ptr CommandBuffer_T -> IO Result) -> Ptr CommandBuffer_T -> IO Result
endCommandBuffer :: forall io
. (MonadIO io)
=>
CommandBuffer
-> io ()
endCommandBuffer :: forall (io :: * -> *). MonadIO io => CommandBuffer -> io ()
endCommandBuffer CommandBuffer
commandBuffer = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
let vkEndCommandBufferPtr :: FunPtr (Ptr CommandBuffer_T -> IO Result)
vkEndCommandBufferPtr = DeviceCmds -> FunPtr (Ptr CommandBuffer_T -> IO Result)
pVkEndCommandBuffer (case CommandBuffer
commandBuffer of CommandBuffer{DeviceCmds
deviceCmds :: DeviceCmds
$sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr (Ptr CommandBuffer_T -> IO Result)
vkEndCommandBufferPtr 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 vkEndCommandBuffer is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
let vkEndCommandBuffer' :: Ptr CommandBuffer_T -> IO Result
vkEndCommandBuffer' = FunPtr (Ptr CommandBuffer_T -> IO Result)
-> Ptr CommandBuffer_T -> IO Result
mkVkEndCommandBuffer FunPtr (Ptr CommandBuffer_T -> IO Result)
vkEndCommandBufferPtr
Result
r <- forall a. String -> IO a -> IO a
traceAroundEvent String
"vkEndCommandBuffer" (Ptr CommandBuffer_T -> IO Result
vkEndCommandBuffer'
(CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)))
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" mkVkResetCommandBuffer
:: FunPtr (Ptr CommandBuffer_T -> CommandBufferResetFlags -> IO Result) -> Ptr CommandBuffer_T -> CommandBufferResetFlags -> IO Result
resetCommandBuffer :: forall io
. (MonadIO io)
=>
CommandBuffer
->
CommandBufferResetFlags
-> io ()
resetCommandBuffer :: forall (io :: * -> *).
MonadIO io =>
CommandBuffer -> CommandBufferResetFlags -> io ()
resetCommandBuffer CommandBuffer
commandBuffer CommandBufferResetFlags
flags = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
let vkResetCommandBufferPtr :: FunPtr
(Ptr CommandBuffer_T -> CommandBufferResetFlags -> IO Result)
vkResetCommandBufferPtr = DeviceCmds
-> FunPtr
(Ptr CommandBuffer_T -> CommandBufferResetFlags -> IO Result)
pVkResetCommandBuffer (case CommandBuffer
commandBuffer of CommandBuffer{DeviceCmds
deviceCmds :: DeviceCmds
$sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
(Ptr CommandBuffer_T -> CommandBufferResetFlags -> IO Result)
vkResetCommandBufferPtr 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 vkResetCommandBuffer is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
let vkResetCommandBuffer' :: Ptr CommandBuffer_T -> CommandBufferResetFlags -> IO Result
vkResetCommandBuffer' = FunPtr
(Ptr CommandBuffer_T -> CommandBufferResetFlags -> IO Result)
-> Ptr CommandBuffer_T -> CommandBufferResetFlags -> IO Result
mkVkResetCommandBuffer FunPtr
(Ptr CommandBuffer_T -> CommandBufferResetFlags -> IO Result)
vkResetCommandBufferPtr
Result
r <- forall a. String -> IO a -> IO a
traceAroundEvent String
"vkResetCommandBuffer" (Ptr CommandBuffer_T -> CommandBufferResetFlags -> IO Result
vkResetCommandBuffer'
(CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer))
(CommandBufferResetFlags
flags))
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))
data CommandBufferAllocateInfo = CommandBufferAllocateInfo
{
CommandBufferAllocateInfo -> CommandPool
commandPool :: CommandPool
,
CommandBufferAllocateInfo -> CommandBufferLevel
level :: CommandBufferLevel
,
CommandBufferAllocateInfo -> Word32
commandBufferCount :: Word32
}
deriving (Typeable, CommandBufferAllocateInfo -> CommandBufferAllocateInfo -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommandBufferAllocateInfo -> CommandBufferAllocateInfo -> Bool
$c/= :: CommandBufferAllocateInfo -> CommandBufferAllocateInfo -> Bool
== :: CommandBufferAllocateInfo -> CommandBufferAllocateInfo -> Bool
$c== :: CommandBufferAllocateInfo -> CommandBufferAllocateInfo -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (CommandBufferAllocateInfo)
#endif
deriving instance Show CommandBufferAllocateInfo
instance ToCStruct CommandBufferAllocateInfo where
withCStruct :: forall b.
CommandBufferAllocateInfo
-> (("pAllocateInfo" ::: Ptr CommandBufferAllocateInfo) -> IO b)
-> IO b
withCStruct CommandBufferAllocateInfo
x ("pAllocateInfo" ::: Ptr CommandBufferAllocateInfo) -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
32 forall a b. (a -> b) -> a -> b
$ \"pAllocateInfo" ::: Ptr CommandBufferAllocateInfo
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pAllocateInfo" ::: Ptr CommandBufferAllocateInfo
p CommandBufferAllocateInfo
x (("pAllocateInfo" ::: Ptr CommandBufferAllocateInfo) -> IO b
f "pAllocateInfo" ::: Ptr CommandBufferAllocateInfo
p)
pokeCStruct :: forall b.
("pAllocateInfo" ::: Ptr CommandBufferAllocateInfo)
-> CommandBufferAllocateInfo -> IO b -> IO b
pokeCStruct "pAllocateInfo" ::: Ptr CommandBufferAllocateInfo
p CommandBufferAllocateInfo{Word32
CommandPool
CommandBufferLevel
commandBufferCount :: Word32
level :: CommandBufferLevel
commandPool :: CommandPool
$sel:level:CommandBufferAllocateInfo :: CommandBufferAllocateInfo -> CommandBufferLevel
$sel:commandPool:CommandBufferAllocateInfo :: CommandBufferAllocateInfo -> CommandPool
$sel:commandBufferCount:CommandBufferAllocateInfo :: CommandBufferAllocateInfo -> Word32
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pAllocateInfo" ::: Ptr CommandBufferAllocateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_COMMAND_BUFFER_ALLOCATE_INFO)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pAllocateInfo" ::: Ptr CommandBufferAllocateInfo
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 (("pAllocateInfo" ::: Ptr CommandBufferAllocateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr CommandPool)) (CommandPool
commandPool)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pAllocateInfo" ::: Ptr CommandBufferAllocateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr CommandBufferLevel)) (CommandBufferLevel
level)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pAllocateInfo" ::: Ptr CommandBufferAllocateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr Word32)) (Word32
commandBufferCount)
IO b
f
cStructSize :: Int
cStructSize = Int
32
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
("pAllocateInfo" ::: Ptr CommandBufferAllocateInfo) -> IO b -> IO b
pokeZeroCStruct "pAllocateInfo" ::: Ptr CommandBufferAllocateInfo
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pAllocateInfo" ::: Ptr CommandBufferAllocateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_COMMAND_BUFFER_ALLOCATE_INFO)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pAllocateInfo" ::: Ptr CommandBufferAllocateInfo
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 (("pAllocateInfo" ::: Ptr CommandBufferAllocateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr CommandPool)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pAllocateInfo" ::: Ptr CommandBufferAllocateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr CommandBufferLevel)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pAllocateInfo" ::: Ptr CommandBufferAllocateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr Word32)) (forall a. Zero a => a
zero)
IO b
f
instance FromCStruct CommandBufferAllocateInfo where
peekCStruct :: ("pAllocateInfo" ::: Ptr CommandBufferAllocateInfo)
-> IO CommandBufferAllocateInfo
peekCStruct "pAllocateInfo" ::: Ptr CommandBufferAllocateInfo
p = do
CommandPool
commandPool <- forall a. Storable a => Ptr a -> IO a
peek @CommandPool (("pAllocateInfo" ::: Ptr CommandBufferAllocateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr CommandPool))
CommandBufferLevel
level <- forall a. Storable a => Ptr a -> IO a
peek @CommandBufferLevel (("pAllocateInfo" ::: Ptr CommandBufferAllocateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr CommandBufferLevel))
Word32
commandBufferCount <- forall a. Storable a => Ptr a -> IO a
peek @Word32 (("pAllocateInfo" ::: Ptr CommandBufferAllocateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr Word32))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ CommandPool
-> CommandBufferLevel -> Word32 -> CommandBufferAllocateInfo
CommandBufferAllocateInfo
CommandPool
commandPool CommandBufferLevel
level Word32
commandBufferCount
instance Storable CommandBufferAllocateInfo where
sizeOf :: CommandBufferAllocateInfo -> Int
sizeOf ~CommandBufferAllocateInfo
_ = Int
32
alignment :: CommandBufferAllocateInfo -> Int
alignment ~CommandBufferAllocateInfo
_ = Int
8
peek :: ("pAllocateInfo" ::: Ptr CommandBufferAllocateInfo)
-> IO CommandBufferAllocateInfo
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: ("pAllocateInfo" ::: Ptr CommandBufferAllocateInfo)
-> CommandBufferAllocateInfo -> IO ()
poke "pAllocateInfo" ::: Ptr CommandBufferAllocateInfo
ptr CommandBufferAllocateInfo
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pAllocateInfo" ::: Ptr CommandBufferAllocateInfo
ptr CommandBufferAllocateInfo
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero CommandBufferAllocateInfo where
zero :: CommandBufferAllocateInfo
zero = CommandPool
-> CommandBufferLevel -> Word32 -> CommandBufferAllocateInfo
CommandBufferAllocateInfo
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
data CommandBufferInheritanceInfo (es :: [Type]) = CommandBufferInheritanceInfo
{
forall (es :: [*]). CommandBufferInheritanceInfo es -> Chain es
next :: Chain es
,
forall (es :: [*]). CommandBufferInheritanceInfo es -> RenderPass
renderPass :: RenderPass
,
forall (es :: [*]). CommandBufferInheritanceInfo es -> Word32
subpass :: Word32
,
forall (es :: [*]). CommandBufferInheritanceInfo es -> Framebuffer
framebuffer :: Framebuffer
,
forall (es :: [*]). CommandBufferInheritanceInfo es -> Bool
occlusionQueryEnable :: Bool
,
forall (es :: [*]).
CommandBufferInheritanceInfo es -> QueryControlFlags
queryFlags :: QueryControlFlags
,
forall (es :: [*]).
CommandBufferInheritanceInfo es -> QueryPipelineStatisticFlags
pipelineStatistics :: QueryPipelineStatisticFlags
}
deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (CommandBufferInheritanceInfo (es :: [Type]))
#endif
deriving instance Show (Chain es) => Show (CommandBufferInheritanceInfo es)
instance Extensible CommandBufferInheritanceInfo where
extensibleTypeName :: String
extensibleTypeName = String
"CommandBufferInheritanceInfo"
setNext :: forall (ds :: [*]) (es :: [*]).
CommandBufferInheritanceInfo ds
-> Chain es -> CommandBufferInheritanceInfo es
setNext CommandBufferInheritanceInfo{Bool
Word32
Chain ds
QueryControlFlags
RenderPass
Framebuffer
QueryPipelineStatisticFlags
pipelineStatistics :: QueryPipelineStatisticFlags
queryFlags :: QueryControlFlags
occlusionQueryEnable :: Bool
framebuffer :: Framebuffer
subpass :: Word32
renderPass :: RenderPass
next :: Chain ds
$sel:pipelineStatistics:CommandBufferInheritanceInfo :: forall (es :: [*]).
CommandBufferInheritanceInfo es -> QueryPipelineStatisticFlags
$sel:queryFlags:CommandBufferInheritanceInfo :: forall (es :: [*]).
CommandBufferInheritanceInfo es -> QueryControlFlags
$sel:occlusionQueryEnable:CommandBufferInheritanceInfo :: forall (es :: [*]). CommandBufferInheritanceInfo es -> Bool
$sel:framebuffer:CommandBufferInheritanceInfo :: forall (es :: [*]). CommandBufferInheritanceInfo es -> Framebuffer
$sel:subpass:CommandBufferInheritanceInfo :: forall (es :: [*]). CommandBufferInheritanceInfo es -> Word32
$sel:renderPass:CommandBufferInheritanceInfo :: forall (es :: [*]). CommandBufferInheritanceInfo es -> RenderPass
$sel:next:CommandBufferInheritanceInfo :: forall (es :: [*]). CommandBufferInheritanceInfo es -> Chain es
..} Chain es
next' = CommandBufferInheritanceInfo{$sel:next:CommandBufferInheritanceInfo :: Chain es
next = Chain es
next', Bool
Word32
QueryControlFlags
RenderPass
Framebuffer
QueryPipelineStatisticFlags
pipelineStatistics :: QueryPipelineStatisticFlags
queryFlags :: QueryControlFlags
occlusionQueryEnable :: Bool
framebuffer :: Framebuffer
subpass :: Word32
renderPass :: RenderPass
$sel:pipelineStatistics:CommandBufferInheritanceInfo :: QueryPipelineStatisticFlags
$sel:queryFlags:CommandBufferInheritanceInfo :: QueryControlFlags
$sel:occlusionQueryEnable:CommandBufferInheritanceInfo :: Bool
$sel:framebuffer:CommandBufferInheritanceInfo :: Framebuffer
$sel:subpass:CommandBufferInheritanceInfo :: Word32
$sel:renderPass:CommandBufferInheritanceInfo :: RenderPass
..}
getNext :: forall (es :: [*]). CommandBufferInheritanceInfo es -> Chain es
getNext CommandBufferInheritanceInfo{Bool
Word32
Chain es
QueryControlFlags
RenderPass
Framebuffer
QueryPipelineStatisticFlags
pipelineStatistics :: QueryPipelineStatisticFlags
queryFlags :: QueryControlFlags
occlusionQueryEnable :: Bool
framebuffer :: Framebuffer
subpass :: Word32
renderPass :: RenderPass
next :: Chain es
$sel:pipelineStatistics:CommandBufferInheritanceInfo :: forall (es :: [*]).
CommandBufferInheritanceInfo es -> QueryPipelineStatisticFlags
$sel:queryFlags:CommandBufferInheritanceInfo :: forall (es :: [*]).
CommandBufferInheritanceInfo es -> QueryControlFlags
$sel:occlusionQueryEnable:CommandBufferInheritanceInfo :: forall (es :: [*]). CommandBufferInheritanceInfo es -> Bool
$sel:framebuffer:CommandBufferInheritanceInfo :: forall (es :: [*]). CommandBufferInheritanceInfo es -> Framebuffer
$sel:subpass:CommandBufferInheritanceInfo :: forall (es :: [*]). CommandBufferInheritanceInfo es -> Word32
$sel:renderPass:CommandBufferInheritanceInfo :: forall (es :: [*]). CommandBufferInheritanceInfo es -> RenderPass
$sel:next:CommandBufferInheritanceInfo :: forall (es :: [*]). CommandBufferInheritanceInfo es -> Chain es
..} = Chain es
next
extends :: forall e b proxy. Typeable e => proxy e -> (Extends CommandBufferInheritanceInfo e => b) -> Maybe b
extends :: forall e b (proxy :: * -> *).
Typeable e =>
proxy e -> (Extends CommandBufferInheritanceInfo e => b) -> Maybe b
extends proxy e
_ Extends CommandBufferInheritanceInfo e => b
f
| Just e :~: MultiviewPerViewAttributesInfoNVX
Refl <- forall {k} (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @MultiviewPerViewAttributesInfoNVX = forall a. a -> Maybe a
Just Extends CommandBufferInheritanceInfo e => b
f
| Just e :~: AttachmentSampleCountInfoAMD
Refl <- forall {k} (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @AttachmentSampleCountInfoAMD = forall a. a -> Maybe a
Just Extends CommandBufferInheritanceInfo e => b
f
| Just e :~: CommandBufferInheritanceRenderingInfo
Refl <- forall {k} (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @CommandBufferInheritanceRenderingInfo = forall a. a -> Maybe a
Just Extends CommandBufferInheritanceInfo e => b
f
| Just e :~: CommandBufferInheritanceViewportScissorInfoNV
Refl <- forall {k} (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @CommandBufferInheritanceViewportScissorInfoNV = forall a. a -> Maybe a
Just Extends CommandBufferInheritanceInfo e => b
f
| Just e :~: CommandBufferInheritanceRenderPassTransformInfoQCOM
Refl <- forall {k} (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @CommandBufferInheritanceRenderPassTransformInfoQCOM = forall a. a -> Maybe a
Just Extends CommandBufferInheritanceInfo e => b
f
| Just e :~: ExternalFormatANDROID
Refl <- forall {k} (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @ExternalFormatANDROID = forall a. a -> Maybe a
Just Extends CommandBufferInheritanceInfo e => b
f
| Just e :~: CommandBufferInheritanceConditionalRenderingInfoEXT
Refl <- forall {k} (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @CommandBufferInheritanceConditionalRenderingInfoEXT = forall a. a -> Maybe a
Just Extends CommandBufferInheritanceInfo e => b
f
| Bool
otherwise = forall a. Maybe a
Nothing
instance ( Extendss CommandBufferInheritanceInfo es
, PokeChain es ) => ToCStruct (CommandBufferInheritanceInfo es) where
withCStruct :: forall b.
CommandBufferInheritanceInfo es
-> (Ptr (CommandBufferInheritanceInfo es) -> IO b) -> IO b
withCStruct CommandBufferInheritanceInfo es
x Ptr (CommandBufferInheritanceInfo es) -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
56 forall a b. (a -> b) -> a -> b
$ \Ptr (CommandBufferInheritanceInfo es)
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr (CommandBufferInheritanceInfo es)
p CommandBufferInheritanceInfo es
x (Ptr (CommandBufferInheritanceInfo es) -> IO b
f Ptr (CommandBufferInheritanceInfo es)
p)
pokeCStruct :: forall b.
Ptr (CommandBufferInheritanceInfo es)
-> CommandBufferInheritanceInfo es -> IO b -> IO b
pokeCStruct Ptr (CommandBufferInheritanceInfo es)
p CommandBufferInheritanceInfo{Bool
Word32
Chain es
QueryControlFlags
RenderPass
Framebuffer
QueryPipelineStatisticFlags
pipelineStatistics :: QueryPipelineStatisticFlags
queryFlags :: QueryControlFlags
occlusionQueryEnable :: Bool
framebuffer :: Framebuffer
subpass :: Word32
renderPass :: RenderPass
next :: Chain es
$sel:pipelineStatistics:CommandBufferInheritanceInfo :: forall (es :: [*]).
CommandBufferInheritanceInfo es -> QueryPipelineStatisticFlags
$sel:queryFlags:CommandBufferInheritanceInfo :: forall (es :: [*]).
CommandBufferInheritanceInfo es -> QueryControlFlags
$sel:occlusionQueryEnable:CommandBufferInheritanceInfo :: forall (es :: [*]). CommandBufferInheritanceInfo es -> Bool
$sel:framebuffer:CommandBufferInheritanceInfo :: forall (es :: [*]). CommandBufferInheritanceInfo es -> Framebuffer
$sel:subpass:CommandBufferInheritanceInfo :: forall (es :: [*]). CommandBufferInheritanceInfo es -> Word32
$sel:renderPass:CommandBufferInheritanceInfo :: forall (es :: [*]). CommandBufferInheritanceInfo es -> RenderPass
$sel:next:CommandBufferInheritanceInfo :: forall (es :: [*]). CommandBufferInheritanceInfo es -> Chain es
..} IO b
f = forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT forall a b. (a -> b) -> a -> b
$ do
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 -> a -> IO ()
poke ((Ptr (CommandBufferInheritanceInfo es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_COMMAND_BUFFER_INHERITANCE_INFO)
Ptr ()
pNext'' <- forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a b. Ptr a -> Ptr b
castPtr forall b c a. (b -> c) -> (a -> b) -> a -> c
. 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 (es :: [*]) a.
PokeChain es =>
Chain es -> (Ptr (Chain es) -> IO a) -> IO a
withChain (Chain es
next)
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 -> a -> IO ()
poke ((Ptr (CommandBufferInheritanceInfo es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) Ptr ()
pNext''
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 -> a -> IO ()
poke ((Ptr (CommandBufferInheritanceInfo es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr RenderPass)) (RenderPass
renderPass)
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 -> a -> IO ()
poke ((Ptr (CommandBufferInheritanceInfo es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Word32)) (Word32
subpass)
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 -> a -> IO ()
poke ((Ptr (CommandBufferInheritanceInfo es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr Framebuffer)) (Framebuffer
framebuffer)
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 -> a -> IO ()
poke ((Ptr (CommandBufferInheritanceInfo es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
occlusionQueryEnable))
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 -> a -> IO ()
poke ((Ptr (CommandBufferInheritanceInfo es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
44 :: Ptr QueryControlFlags)) (QueryControlFlags
queryFlags)
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 -> a -> IO ()
poke ((Ptr (CommandBufferInheritanceInfo es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48 :: Ptr QueryPipelineStatisticFlags)) (QueryPipelineStatisticFlags
pipelineStatistics)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ IO b
f
cStructSize :: Int
cStructSize = Int
56
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b. Ptr (CommandBufferInheritanceInfo es) -> IO b -> IO b
pokeZeroCStruct Ptr (CommandBufferInheritanceInfo es)
p IO b
f = forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT forall a b. (a -> b) -> a -> b
$ do
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 -> a -> IO ()
poke ((Ptr (CommandBufferInheritanceInfo es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_COMMAND_BUFFER_INHERITANCE_INFO)
Ptr ()
pNext' <- forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a b. Ptr a -> Ptr b
castPtr forall b c a. (b -> c) -> (a -> b) -> a -> c
. 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 (es :: [*]) a.
PokeChain es =>
(Ptr (Chain es) -> IO a) -> IO a
withZeroChain @es
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 -> a -> IO ()
poke ((Ptr (CommandBufferInheritanceInfo es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) Ptr ()
pNext'
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 -> a -> IO ()
poke ((Ptr (CommandBufferInheritanceInfo es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Word32)) (forall a. Zero a => a
zero)
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 -> a -> IO ()
poke ((Ptr (CommandBufferInheritanceInfo es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ IO b
f
instance ( Extendss CommandBufferInheritanceInfo es
, PeekChain es ) => FromCStruct (CommandBufferInheritanceInfo es) where
peekCStruct :: Ptr (CommandBufferInheritanceInfo es)
-> IO (CommandBufferInheritanceInfo es)
peekCStruct Ptr (CommandBufferInheritanceInfo es)
p = do
Ptr ()
pNext <- forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) ((Ptr (CommandBufferInheritanceInfo es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ())))
Chain es
next <- forall (es :: [*]). PeekChain es => Ptr (Chain es) -> IO (Chain es)
peekChain (forall a b. Ptr a -> Ptr b
castPtr Ptr ()
pNext)
RenderPass
renderPass <- forall a. Storable a => Ptr a -> IO a
peek @RenderPass ((Ptr (CommandBufferInheritanceInfo es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr RenderPass))
Word32
subpass <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr (CommandBufferInheritanceInfo es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Word32))
Framebuffer
framebuffer <- forall a. Storable a => Ptr a -> IO a
peek @Framebuffer ((Ptr (CommandBufferInheritanceInfo es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr Framebuffer))
Bool32
occlusionQueryEnable <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr (CommandBufferInheritanceInfo es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr Bool32))
QueryControlFlags
queryFlags <- forall a. Storable a => Ptr a -> IO a
peek @QueryControlFlags ((Ptr (CommandBufferInheritanceInfo es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
44 :: Ptr QueryControlFlags))
QueryPipelineStatisticFlags
pipelineStatistics <- forall a. Storable a => Ptr a -> IO a
peek @QueryPipelineStatisticFlags ((Ptr (CommandBufferInheritanceInfo es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48 :: Ptr QueryPipelineStatisticFlags))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (es :: [*]).
Chain es
-> RenderPass
-> Word32
-> Framebuffer
-> Bool
-> QueryControlFlags
-> QueryPipelineStatisticFlags
-> CommandBufferInheritanceInfo es
CommandBufferInheritanceInfo
Chain es
next
RenderPass
renderPass
Word32
subpass
Framebuffer
framebuffer
(Bool32 -> Bool
bool32ToBool Bool32
occlusionQueryEnable)
QueryControlFlags
queryFlags
QueryPipelineStatisticFlags
pipelineStatistics
instance es ~ '[] => Zero (CommandBufferInheritanceInfo es) where
zero :: CommandBufferInheritanceInfo es
zero = forall (es :: [*]).
Chain es
-> RenderPass
-> Word32
-> Framebuffer
-> Bool
-> QueryControlFlags
-> QueryPipelineStatisticFlags
-> CommandBufferInheritanceInfo es
CommandBufferInheritanceInfo
()
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
data CommandBufferBeginInfo (es :: [Type]) = CommandBufferBeginInfo
{
forall (es :: [*]). CommandBufferBeginInfo es -> Chain es
next :: Chain es
,
forall (es :: [*]).
CommandBufferBeginInfo es -> CommandBufferUsageFlags
flags :: CommandBufferUsageFlags
,
forall (es :: [*]).
CommandBufferBeginInfo es
-> Maybe (SomeStruct CommandBufferInheritanceInfo)
inheritanceInfo :: Maybe (SomeStruct CommandBufferInheritanceInfo)
}
deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (CommandBufferBeginInfo (es :: [Type]))
#endif
deriving instance Show (Chain es) => Show (CommandBufferBeginInfo es)
instance Extensible CommandBufferBeginInfo where
extensibleTypeName :: String
extensibleTypeName = String
"CommandBufferBeginInfo"
setNext :: forall (ds :: [*]) (es :: [*]).
CommandBufferBeginInfo ds -> Chain es -> CommandBufferBeginInfo es
setNext CommandBufferBeginInfo{Maybe (SomeStruct CommandBufferInheritanceInfo)
Chain ds
CommandBufferUsageFlags
inheritanceInfo :: Maybe (SomeStruct CommandBufferInheritanceInfo)
flags :: CommandBufferUsageFlags
next :: Chain ds
$sel:inheritanceInfo:CommandBufferBeginInfo :: forall (es :: [*]).
CommandBufferBeginInfo es
-> Maybe (SomeStruct CommandBufferInheritanceInfo)
$sel:flags:CommandBufferBeginInfo :: forall (es :: [*]).
CommandBufferBeginInfo es -> CommandBufferUsageFlags
$sel:next:CommandBufferBeginInfo :: forall (es :: [*]). CommandBufferBeginInfo es -> Chain es
..} Chain es
next' = CommandBufferBeginInfo{$sel:next:CommandBufferBeginInfo :: Chain es
next = Chain es
next', Maybe (SomeStruct CommandBufferInheritanceInfo)
CommandBufferUsageFlags
inheritanceInfo :: Maybe (SomeStruct CommandBufferInheritanceInfo)
flags :: CommandBufferUsageFlags
$sel:inheritanceInfo:CommandBufferBeginInfo :: Maybe (SomeStruct CommandBufferInheritanceInfo)
$sel:flags:CommandBufferBeginInfo :: CommandBufferUsageFlags
..}
getNext :: forall (es :: [*]). CommandBufferBeginInfo es -> Chain es
getNext CommandBufferBeginInfo{Maybe (SomeStruct CommandBufferInheritanceInfo)
Chain es
CommandBufferUsageFlags
inheritanceInfo :: Maybe (SomeStruct CommandBufferInheritanceInfo)
flags :: CommandBufferUsageFlags
next :: Chain es
$sel:inheritanceInfo:CommandBufferBeginInfo :: forall (es :: [*]).
CommandBufferBeginInfo es
-> Maybe (SomeStruct CommandBufferInheritanceInfo)
$sel:flags:CommandBufferBeginInfo :: forall (es :: [*]).
CommandBufferBeginInfo es -> CommandBufferUsageFlags
$sel:next:CommandBufferBeginInfo :: forall (es :: [*]). CommandBufferBeginInfo es -> Chain es
..} = Chain es
next
extends :: forall e b proxy. Typeable e => proxy e -> (Extends CommandBufferBeginInfo e => b) -> Maybe b
extends :: forall e b (proxy :: * -> *).
Typeable e =>
proxy e -> (Extends CommandBufferBeginInfo e => b) -> Maybe b
extends proxy e
_ Extends CommandBufferBeginInfo e => b
f
| Just e :~: DeviceGroupCommandBufferBeginInfo
Refl <- forall {k} (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @DeviceGroupCommandBufferBeginInfo = forall a. a -> Maybe a
Just Extends CommandBufferBeginInfo e => b
f
| Bool
otherwise = forall a. Maybe a
Nothing
instance ( Extendss CommandBufferBeginInfo es
, PokeChain es ) => ToCStruct (CommandBufferBeginInfo es) where
withCStruct :: forall b.
CommandBufferBeginInfo es
-> (Ptr (CommandBufferBeginInfo es) -> IO b) -> IO b
withCStruct CommandBufferBeginInfo es
x Ptr (CommandBufferBeginInfo es) -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
32 forall a b. (a -> b) -> a -> b
$ \Ptr (CommandBufferBeginInfo es)
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr (CommandBufferBeginInfo es)
p CommandBufferBeginInfo es
x (Ptr (CommandBufferBeginInfo es) -> IO b
f Ptr (CommandBufferBeginInfo es)
p)
pokeCStruct :: forall b.
Ptr (CommandBufferBeginInfo es)
-> CommandBufferBeginInfo es -> IO b -> IO b
pokeCStruct Ptr (CommandBufferBeginInfo es)
p CommandBufferBeginInfo{Maybe (SomeStruct CommandBufferInheritanceInfo)
Chain es
CommandBufferUsageFlags
inheritanceInfo :: Maybe (SomeStruct CommandBufferInheritanceInfo)
flags :: CommandBufferUsageFlags
next :: Chain es
$sel:inheritanceInfo:CommandBufferBeginInfo :: forall (es :: [*]).
CommandBufferBeginInfo es
-> Maybe (SomeStruct CommandBufferInheritanceInfo)
$sel:flags:CommandBufferBeginInfo :: forall (es :: [*]).
CommandBufferBeginInfo es -> CommandBufferUsageFlags
$sel:next:CommandBufferBeginInfo :: forall (es :: [*]). CommandBufferBeginInfo es -> Chain es
..} IO b
f = forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT forall a b. (a -> b) -> a -> b
$ do
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 -> a -> IO ()
poke ((Ptr (CommandBufferBeginInfo es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_COMMAND_BUFFER_BEGIN_INFO)
Ptr ()
pNext'' <- forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a b. Ptr a -> Ptr b
castPtr forall b c a. (b -> c) -> (a -> b) -> a -> c
. 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 (es :: [*]) a.
PokeChain es =>
Chain es -> (Ptr (Chain es) -> IO a) -> IO a
withChain (Chain es
next)
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 -> a -> IO ()
poke ((Ptr (CommandBufferBeginInfo es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) Ptr ()
pNext''
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 -> a -> IO ()
poke ((Ptr (CommandBufferBeginInfo es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr CommandBufferUsageFlags)) (CommandBufferUsageFlags
flags)
Ptr (CommandBufferInheritanceInfo '[])
pInheritanceInfo'' <- case (Maybe (SomeStruct CommandBufferInheritanceInfo)
inheritanceInfo) of
Maybe (SomeStruct CommandBufferInheritanceInfo)
Nothing -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. Ptr a
nullPtr
Just SomeStruct CommandBufferInheritanceInfo
j -> forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT @_ @_ @(Ptr (CommandBufferInheritanceInfo '[])) forall a b. (a -> b) -> a -> b
$ \Ptr (CommandBufferInheritanceInfo '[]) -> IO b
cont -> forall (a :: [*] -> *) b.
(forall (es :: [*]).
(Extendss a es, PokeChain es) =>
ToCStruct (a es)) =>
SomeStruct a
-> (forall (es :: [*]).
(Extendss a es, PokeChain es) =>
Ptr (a es) -> IO b)
-> IO b
withSomeCStruct @CommandBufferInheritanceInfo (SomeStruct CommandBufferInheritanceInfo
j) (Ptr (CommandBufferInheritanceInfo '[]) -> IO b
cont forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. Ptr a -> Ptr b
castPtr)
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 -> a -> IO ()
poke ((Ptr (CommandBufferBeginInfo es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr (Ptr (CommandBufferInheritanceInfo _)))) Ptr (CommandBufferInheritanceInfo '[])
pInheritanceInfo''
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ IO b
f
cStructSize :: Int
cStructSize = Int
32
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b. Ptr (CommandBufferBeginInfo es) -> IO b -> IO b
pokeZeroCStruct Ptr (CommandBufferBeginInfo es)
p IO b
f = forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT forall a b. (a -> b) -> a -> b
$ do
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 -> a -> IO ()
poke ((Ptr (CommandBufferBeginInfo es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_COMMAND_BUFFER_BEGIN_INFO)
Ptr ()
pNext' <- forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a b. Ptr a -> Ptr b
castPtr forall b c a. (b -> c) -> (a -> b) -> a -> c
. 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 (es :: [*]) a.
PokeChain es =>
(Ptr (Chain es) -> IO a) -> IO a
withZeroChain @es
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 -> a -> IO ()
poke ((Ptr (CommandBufferBeginInfo es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) Ptr ()
pNext'
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ IO b
f
instance ( Extendss CommandBufferBeginInfo es
, PeekChain es ) => FromCStruct (CommandBufferBeginInfo es) where
peekCStruct :: Ptr (CommandBufferBeginInfo es) -> IO (CommandBufferBeginInfo es)
peekCStruct Ptr (CommandBufferBeginInfo es)
p = do
Ptr ()
pNext <- forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) ((Ptr (CommandBufferBeginInfo es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ())))
Chain es
next <- forall (es :: [*]). PeekChain es => Ptr (Chain es) -> IO (Chain es)
peekChain (forall a b. Ptr a -> Ptr b
castPtr Ptr ()
pNext)
CommandBufferUsageFlags
flags <- forall a. Storable a => Ptr a -> IO a
peek @CommandBufferUsageFlags ((Ptr (CommandBufferBeginInfo es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr CommandBufferUsageFlags))
Ptr (CommandBufferInheritanceInfo Any)
pInheritanceInfo <- forall a. Storable a => Ptr a -> IO a
peek @(Ptr (CommandBufferInheritanceInfo _)) ((Ptr (CommandBufferBeginInfo es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr (Ptr (CommandBufferInheritanceInfo _))))
Maybe (SomeStruct CommandBufferInheritanceInfo)
pInheritanceInfo' <- forall a b. (Ptr a -> IO b) -> Ptr a -> IO (Maybe b)
maybePeek (\Ptr (CommandBufferInheritanceInfo Any)
j -> forall (a :: [*] -> *).
(Extensible a,
forall (es :: [*]).
(Extendss a es, PeekChain es) =>
FromCStruct (a es)) =>
Ptr (SomeStruct a) -> IO (SomeStruct a)
peekSomeCStruct (forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions (Ptr (CommandBufferInheritanceInfo Any)
j))) Ptr (CommandBufferInheritanceInfo Any)
pInheritanceInfo
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (es :: [*]).
Chain es
-> CommandBufferUsageFlags
-> Maybe (SomeStruct CommandBufferInheritanceInfo)
-> CommandBufferBeginInfo es
CommandBufferBeginInfo
Chain es
next CommandBufferUsageFlags
flags Maybe (SomeStruct CommandBufferInheritanceInfo)
pInheritanceInfo'
instance es ~ '[] => Zero (CommandBufferBeginInfo es) where
zero :: CommandBufferBeginInfo es
zero = forall (es :: [*]).
Chain es
-> CommandBufferUsageFlags
-> Maybe (SomeStruct CommandBufferInheritanceInfo)
-> CommandBufferBeginInfo es
CommandBufferBeginInfo
()
forall a. Zero a => a
zero
forall a. Maybe a
Nothing