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