Safe Haskell | None |
---|---|
Language | Haskell2010 |
Gpu.Vulkan.CommandBuffer.Core
Synopsis
- allocateCs :: D -> Ptr AllocateInfo -> Ptr C -> IO Int32
- freeCs :: D -> C -> Word32 -> Ptr C -> IO ()
- type C = Ptr CTag
- type PtrC = Ptr C
- data AllocateInfo
- pattern AllocateInfo :: () -> PtrVoid -> C -> Word32 -> Word32 -> AllocateInfo
- allocateInfoSType :: AllocateInfo -> ()
- allocateInfoPNext :: AllocateInfo -> PtrVoid
- allocateInfoCommandPool :: AllocateInfo -> C
- allocateInfoLevel :: AllocateInfo -> Word32
- levelPrimary :: Word32
- allocateInfoCommandBufferCount :: AllocateInfo -> Word32
- begin :: C -> Ptr BeginInfo -> IO Int32
- end :: C -> IO Int32
- reset :: C -> Word32 -> IO Int32
- data BeginInfo
- pattern BeginInfo :: () -> PtrVoid -> Word32 -> PtrInheritanceInfo -> BeginInfo
- beginInfoSType :: BeginInfo -> ()
- beginInfoPNext :: BeginInfo -> PtrVoid
- beginInfoFlags :: BeginInfo -> Word32
- beginInfoPInheritanceInfo :: BeginInfo -> PtrInheritanceInfo
- data InheritanceInfo
- pattern InheritanceInfo :: () -> PtrVoid -> R -> Word32 -> F -> Word32 -> Word32 -> Word32 -> InheritanceInfo
- inheritanceInfoSType :: InheritanceInfo -> ()
- inheritanceInfoPNext :: InheritanceInfo -> PtrVoid
- inheritanceInfoRenderPass :: InheritanceInfo -> R
- inheritanceInfoSubpass :: InheritanceInfo -> Word32
- inheritanceInfoFramebuffer :: InheritanceInfo -> F
- inheritanceInfoOcclusionQueryEnable :: InheritanceInfo -> Word32
- inheritanceInfoQueryFlags :: InheritanceInfo -> Word32
- inheritanceInfoPipelineStatistics :: InheritanceInfo -> Word32
- data SubmitInfo
- type PtrSubmitInfo = Ptr SubmitInfo
- pattern SubmitInfo :: () -> PtrVoid -> C -> Word32 -> SubmitInfo
- submitInfoSType :: SubmitInfo -> ()
- submitInfoPNext :: SubmitInfo -> PtrVoid
- submitInfoCommandBuffer :: SubmitInfo -> C
- submitInfoDeviceMask :: SubmitInfo -> Word32
ALLOCATE AND FREE
allocateCs :: D -> Ptr AllocateInfo -> Ptr C -> IO Int32 Source #
data AllocateInfo Source #
Instances
Storable AllocateInfo Source # | |
Defined in Gpu.Vulkan.CommandBuffer.Core Methods sizeOf :: AllocateInfo -> Int # alignment :: AllocateInfo -> Int # peekElemOff :: Ptr AllocateInfo -> Int -> IO AllocateInfo # pokeElemOff :: Ptr AllocateInfo -> Int -> AllocateInfo -> IO () # peekByteOff :: Ptr b -> Int -> IO AllocateInfo # pokeByteOff :: Ptr b -> Int -> AllocateInfo -> IO () # peek :: Ptr AllocateInfo -> IO AllocateInfo # poke :: Ptr AllocateInfo -> AllocateInfo -> IO () # | |
Show AllocateInfo Source # | |
Defined in Gpu.Vulkan.CommandBuffer.Core Methods showsPrec :: Int -> AllocateInfo -> ShowS # show :: AllocateInfo -> String # showList :: [AllocateInfo] -> ShowS # |
pattern AllocateInfo :: () -> PtrVoid -> C -> Word32 -> Word32 -> AllocateInfo Source #
allocateInfoSType :: AllocateInfo -> () Source #
BEGIN, END AND RESET
Instances
Storable BeginInfo Source # | |
Defined in Gpu.Vulkan.CommandBuffer.Core | |
Show BeginInfo Source # | |
beginInfoSType :: BeginInfo -> () Source #
beginInfoPNext :: BeginInfo -> PtrVoid Source #
beginInfoFlags :: BeginInfo -> Word32 Source #
beginInfoPInheritanceInfo :: BeginInfo -> PtrInheritanceInfo Source #
INHERITANCE INFO
data InheritanceInfo Source #
Instances
Storable InheritanceInfo Source # | |
Defined in Gpu.Vulkan.CommandBuffer.Core Methods sizeOf :: InheritanceInfo -> Int # alignment :: InheritanceInfo -> Int # peekElemOff :: Ptr InheritanceInfo -> Int -> IO InheritanceInfo # pokeElemOff :: Ptr InheritanceInfo -> Int -> InheritanceInfo -> IO () # peekByteOff :: Ptr b -> Int -> IO InheritanceInfo # pokeByteOff :: Ptr b -> Int -> InheritanceInfo -> IO () # peek :: Ptr InheritanceInfo -> IO InheritanceInfo # poke :: Ptr InheritanceInfo -> InheritanceInfo -> IO () # | |
Show InheritanceInfo Source # | |
Defined in Gpu.Vulkan.CommandBuffer.Core Methods showsPrec :: Int -> InheritanceInfo -> ShowS # show :: InheritanceInfo -> String # showList :: [InheritanceInfo] -> ShowS # |
pattern InheritanceInfo :: () -> PtrVoid -> R -> Word32 -> F -> Word32 -> Word32 -> Word32 -> InheritanceInfo Source #
inheritanceInfoSType :: InheritanceInfo -> () Source #
SUBMIT INFO
data SubmitInfo Source #
Instances
Storable SubmitInfo Source # | |
Defined in Gpu.Vulkan.CommandBuffer.Core Methods sizeOf :: SubmitInfo -> Int # alignment :: SubmitInfo -> Int # peekElemOff :: Ptr SubmitInfo -> Int -> IO SubmitInfo # pokeElemOff :: Ptr SubmitInfo -> Int -> SubmitInfo -> IO () # peekByteOff :: Ptr b -> Int -> IO SubmitInfo # pokeByteOff :: Ptr b -> Int -> SubmitInfo -> IO () # peek :: Ptr SubmitInfo -> IO SubmitInfo # poke :: Ptr SubmitInfo -> SubmitInfo -> IO () # | |
Show SubmitInfo Source # | |
Defined in Gpu.Vulkan.CommandBuffer.Core Methods showsPrec :: Int -> SubmitInfo -> ShowS # show :: SubmitInfo -> String # showList :: [SubmitInfo] -> ShowS # |
type PtrSubmitInfo = Ptr SubmitInfo Source #
pattern SubmitInfo :: () -> PtrVoid -> C -> Word32 -> SubmitInfo Source #
submitInfoSType :: SubmitInfo -> () Source #
submitInfoPNext :: SubmitInfo -> PtrVoid Source #