{-# language Strict #-} {-# language CPP #-} {-# language GeneralizedNewtypeDeriving #-} {-# language PatternSynonyms #-} {-# language DataKinds #-} {-# language TypeOperators #-} {-# language DuplicateRecordFields #-} module Graphics.Vulkan.Core11.Promoted_from_VK_KHR_device_group ( VkPeerMemoryFeatureFlagBits(..) , pattern VK_PEER_MEMORY_FEATURE_COPY_SRC_BIT , pattern VK_PEER_MEMORY_FEATURE_COPY_DST_BIT , pattern VK_PEER_MEMORY_FEATURE_GENERIC_SRC_BIT , pattern VK_PEER_MEMORY_FEATURE_GENERIC_DST_BIT , VkMemoryAllocateFlagBits(..) , pattern VK_MEMORY_ALLOCATE_DEVICE_MASK_BIT , pattern VK_STRUCTURE_TYPE_MEMORY_ALLOCATE_FLAGS_INFO , pattern VK_STRUCTURE_TYPE_DEVICE_GROUP_RENDER_PASS_BEGIN_INFO , pattern VK_STRUCTURE_TYPE_DEVICE_GROUP_COMMAND_BUFFER_BEGIN_INFO , pattern VK_STRUCTURE_TYPE_DEVICE_GROUP_SUBMIT_INFO , pattern VK_STRUCTURE_TYPE_DEVICE_GROUP_BIND_SPARSE_INFO , pattern VK_PIPELINE_CREATE_VIEW_INDEX_FROM_DEVICE_INDEX_BIT , pattern VK_PIPELINE_CREATE_DISPATCH_BASE , pattern VK_DEPENDENCY_DEVICE_GROUP_BIT , vkGetDeviceGroupPeerMemoryFeatures , vkCmdSetDeviceMask , vkCmdDispatchBase , VkMemoryAllocateFlagsInfo(..) , VkDeviceGroupRenderPassBeginInfo(..) , VkDeviceGroupCommandBufferBeginInfo(..) , VkDeviceGroupSubmitInfo(..) , VkDeviceGroupBindSparseInfo(..) , VkPeerMemoryFeatureFlags , VkMemoryAllocateFlags ) where import Data.Bits ( Bits , FiniteBits ) import Data.Word ( Word32 ) import Foreign.Ptr ( plusPtr , Ptr ) import Foreign.Storable ( Storable(..) , Storable ) import GHC.Read ( expectP , choose ) import Graphics.Vulkan.NamedType ( (:::) ) import Text.ParserCombinators.ReadPrec ( (+++) , prec , step ) import Text.Read ( Read(..) , parens ) import Text.Read.Lex ( Lexeme(Ident) ) import Graphics.Vulkan.Core10.Core ( VkStructureType(..) , VkFlags ) import Graphics.Vulkan.Core10.DeviceInitialization ( VkDevice ) import Graphics.Vulkan.Core10.Pass ( VkDependencyFlagBits(..) ) import Graphics.Vulkan.Core10.Pipeline ( VkRect2D(..) , VkPipelineCreateFlagBits(..) ) import Graphics.Vulkan.Core10.Queue ( VkCommandBuffer ) -- ** VkPeerMemoryFeatureFlagBits -- | VkPeerMemoryFeatureFlagBits - Bitmask specifying supported peer memory -- features newtype VkPeerMemoryFeatureFlagBits = VkPeerMemoryFeatureFlagBits VkFlags deriving (Eq, Ord, Storable, Bits, FiniteBits) instance Show VkPeerMemoryFeatureFlagBits where showsPrec _ VK_PEER_MEMORY_FEATURE_COPY_SRC_BIT = showString "VK_PEER_MEMORY_FEATURE_COPY_SRC_BIT" showsPrec _ VK_PEER_MEMORY_FEATURE_COPY_DST_BIT = showString "VK_PEER_MEMORY_FEATURE_COPY_DST_BIT" showsPrec _ VK_PEER_MEMORY_FEATURE_GENERIC_SRC_BIT = showString "VK_PEER_MEMORY_FEATURE_GENERIC_SRC_BIT" showsPrec _ VK_PEER_MEMORY_FEATURE_GENERIC_DST_BIT = showString "VK_PEER_MEMORY_FEATURE_GENERIC_DST_BIT" showsPrec p (VkPeerMemoryFeatureFlagBits x) = showParen (p >= 11) (showString "VkPeerMemoryFeatureFlagBits " . showsPrec 11 x) instance Read VkPeerMemoryFeatureFlagBits where readPrec = parens ( choose [ ("VK_PEER_MEMORY_FEATURE_COPY_SRC_BIT", pure VK_PEER_MEMORY_FEATURE_COPY_SRC_BIT) , ("VK_PEER_MEMORY_FEATURE_COPY_DST_BIT", pure VK_PEER_MEMORY_FEATURE_COPY_DST_BIT) , ("VK_PEER_MEMORY_FEATURE_GENERIC_SRC_BIT", pure VK_PEER_MEMORY_FEATURE_GENERIC_SRC_BIT) , ("VK_PEER_MEMORY_FEATURE_GENERIC_DST_BIT", pure VK_PEER_MEMORY_FEATURE_GENERIC_DST_BIT) ] +++ prec 10 (do expectP (Ident "VkPeerMemoryFeatureFlagBits") v <- step readPrec pure (VkPeerMemoryFeatureFlagBits v) ) ) -- No documentation found for Nested "VkPeerMemoryFeatureFlagBits" "VK_PEER_MEMORY_FEATURE_COPY_SRC_BIT" pattern VK_PEER_MEMORY_FEATURE_COPY_SRC_BIT :: VkPeerMemoryFeatureFlagBits pattern VK_PEER_MEMORY_FEATURE_COPY_SRC_BIT = VkPeerMemoryFeatureFlagBits 0x00000001 -- No documentation found for Nested "VkPeerMemoryFeatureFlagBits" "VK_PEER_MEMORY_FEATURE_COPY_DST_BIT" pattern VK_PEER_MEMORY_FEATURE_COPY_DST_BIT :: VkPeerMemoryFeatureFlagBits pattern VK_PEER_MEMORY_FEATURE_COPY_DST_BIT = VkPeerMemoryFeatureFlagBits 0x00000002 -- No documentation found for Nested "VkPeerMemoryFeatureFlagBits" "VK_PEER_MEMORY_FEATURE_GENERIC_SRC_BIT" pattern VK_PEER_MEMORY_FEATURE_GENERIC_SRC_BIT :: VkPeerMemoryFeatureFlagBits pattern VK_PEER_MEMORY_FEATURE_GENERIC_SRC_BIT = VkPeerMemoryFeatureFlagBits 0x00000004 -- No documentation found for Nested "VkPeerMemoryFeatureFlagBits" "VK_PEER_MEMORY_FEATURE_GENERIC_DST_BIT" pattern VK_PEER_MEMORY_FEATURE_GENERIC_DST_BIT :: VkPeerMemoryFeatureFlagBits pattern VK_PEER_MEMORY_FEATURE_GENERIC_DST_BIT = VkPeerMemoryFeatureFlagBits 0x00000008 -- ** VkMemoryAllocateFlagBits -- | VkMemoryAllocateFlagBits - Bitmask specifying flags for a device memory -- allocation newtype VkMemoryAllocateFlagBits = VkMemoryAllocateFlagBits VkFlags deriving (Eq, Ord, Storable, Bits, FiniteBits) instance Show VkMemoryAllocateFlagBits where showsPrec _ VK_MEMORY_ALLOCATE_DEVICE_MASK_BIT = showString "VK_MEMORY_ALLOCATE_DEVICE_MASK_BIT" showsPrec p (VkMemoryAllocateFlagBits x) = showParen (p >= 11) (showString "VkMemoryAllocateFlagBits " . showsPrec 11 x) instance Read VkMemoryAllocateFlagBits where readPrec = parens ( choose [ ("VK_MEMORY_ALLOCATE_DEVICE_MASK_BIT", pure VK_MEMORY_ALLOCATE_DEVICE_MASK_BIT) ] +++ prec 10 (do expectP (Ident "VkMemoryAllocateFlagBits") v <- step readPrec pure (VkMemoryAllocateFlagBits v) ) ) -- No documentation found for Nested "VkMemoryAllocateFlagBits" "VK_MEMORY_ALLOCATE_DEVICE_MASK_BIT" pattern VK_MEMORY_ALLOCATE_DEVICE_MASK_BIT :: VkMemoryAllocateFlagBits pattern VK_MEMORY_ALLOCATE_DEVICE_MASK_BIT = VkMemoryAllocateFlagBits 0x00000001 -- No documentation found for Nested "VkStructureType" "VK_STRUCTURE_TYPE_MEMORY_ALLOCATE_FLAGS_INFO" pattern VK_STRUCTURE_TYPE_MEMORY_ALLOCATE_FLAGS_INFO :: VkStructureType pattern VK_STRUCTURE_TYPE_MEMORY_ALLOCATE_FLAGS_INFO = VkStructureType 1000060000 -- No documentation found for Nested "VkStructureType" "VK_STRUCTURE_TYPE_DEVICE_GROUP_RENDER_PASS_BEGIN_INFO" pattern VK_STRUCTURE_TYPE_DEVICE_GROUP_RENDER_PASS_BEGIN_INFO :: VkStructureType pattern VK_STRUCTURE_TYPE_DEVICE_GROUP_RENDER_PASS_BEGIN_INFO = VkStructureType 1000060003 -- No documentation found for Nested "VkStructureType" "VK_STRUCTURE_TYPE_DEVICE_GROUP_COMMAND_BUFFER_BEGIN_INFO" pattern VK_STRUCTURE_TYPE_DEVICE_GROUP_COMMAND_BUFFER_BEGIN_INFO :: VkStructureType pattern VK_STRUCTURE_TYPE_DEVICE_GROUP_COMMAND_BUFFER_BEGIN_INFO = VkStructureType 1000060004 -- No documentation found for Nested "VkStructureType" "VK_STRUCTURE_TYPE_DEVICE_GROUP_SUBMIT_INFO" pattern VK_STRUCTURE_TYPE_DEVICE_GROUP_SUBMIT_INFO :: VkStructureType pattern VK_STRUCTURE_TYPE_DEVICE_GROUP_SUBMIT_INFO = VkStructureType 1000060005 -- No documentation found for Nested "VkStructureType" "VK_STRUCTURE_TYPE_DEVICE_GROUP_BIND_SPARSE_INFO" pattern VK_STRUCTURE_TYPE_DEVICE_GROUP_BIND_SPARSE_INFO :: VkStructureType pattern VK_STRUCTURE_TYPE_DEVICE_GROUP_BIND_SPARSE_INFO = VkStructureType 1000060006 -- No documentation found for Nested "VkPipelineCreateFlagBits" "VK_PIPELINE_CREATE_VIEW_INDEX_FROM_DEVICE_INDEX_BIT" pattern VK_PIPELINE_CREATE_VIEW_INDEX_FROM_DEVICE_INDEX_BIT :: VkPipelineCreateFlagBits pattern VK_PIPELINE_CREATE_VIEW_INDEX_FROM_DEVICE_INDEX_BIT = VkPipelineCreateFlagBits 0x00000008 -- No documentation found for Nested "VkPipelineCreateFlagBits" "VK_PIPELINE_CREATE_DISPATCH_BASE" pattern VK_PIPELINE_CREATE_DISPATCH_BASE :: VkPipelineCreateFlagBits pattern VK_PIPELINE_CREATE_DISPATCH_BASE = VkPipelineCreateFlagBits 0x00000010 -- No documentation found for Nested "VkDependencyFlagBits" "VK_DEPENDENCY_DEVICE_GROUP_BIT" pattern VK_DEPENDENCY_DEVICE_GROUP_BIT :: VkDependencyFlagBits pattern VK_DEPENDENCY_DEVICE_GROUP_BIT = VkDependencyFlagBits 0x00000004 -- | vkGetDeviceGroupPeerMemoryFeatures - Query supported peer memory -- features of a device foreign import ccall "vkGetDeviceGroupPeerMemoryFeatures" vkGetDeviceGroupPeerMemoryFeatures :: ("device" ::: VkDevice) -> ("heapIndex" ::: Word32) -> ("localDeviceIndex" ::: Word32) -> ("remoteDeviceIndex" ::: Word32) -> ("pPeerMemoryFeatures" ::: Ptr VkPeerMemoryFeatureFlags) -> IO () -- | vkCmdSetDeviceMask - Modify device mask of a command buffer foreign import ccall "vkCmdSetDeviceMask" vkCmdSetDeviceMask :: ("commandBuffer" ::: VkCommandBuffer) -> ("deviceMask" ::: Word32) -> IO () -- | vkCmdDispatchBase - Dispatch compute work items foreign import ccall "vkCmdDispatchBase" vkCmdDispatchBase :: ("commandBuffer" ::: VkCommandBuffer) -> ("baseGroupX" ::: Word32) -> ("baseGroupY" ::: Word32) -> ("baseGroupZ" ::: Word32) -> ("groupCountX" ::: Word32) -> ("groupCountY" ::: Word32) -> ("groupCountZ" ::: Word32) -> IO () -- | VkMemoryAllocateFlagsInfo - Structure controlling how many instances of -- memory will be allocated data VkMemoryAllocateFlagsInfo = VkMemoryAllocateFlagsInfo { -- No documentation found for Nested "VkMemoryAllocateFlagsInfo" "vkSType" vkSType :: VkStructureType , -- No documentation found for Nested "VkMemoryAllocateFlagsInfo" "vkPNext" vkPNext :: Ptr () , -- No documentation found for Nested "VkMemoryAllocateFlagsInfo" "vkFlags" vkFlags :: VkMemoryAllocateFlags , -- No documentation found for Nested "VkMemoryAllocateFlagsInfo" "vkDeviceMask" vkDeviceMask :: Word32 } deriving (Eq, Show) instance Storable VkMemoryAllocateFlagsInfo where sizeOf ~_ = 24 alignment ~_ = 8 peek ptr = VkMemoryAllocateFlagsInfo <$> peek (ptr `plusPtr` 0) <*> peek (ptr `plusPtr` 8) <*> peek (ptr `plusPtr` 16) <*> peek (ptr `plusPtr` 20) poke ptr poked = poke (ptr `plusPtr` 0) (vkSType (poked :: VkMemoryAllocateFlagsInfo)) *> poke (ptr `plusPtr` 8) (vkPNext (poked :: VkMemoryAllocateFlagsInfo)) *> poke (ptr `plusPtr` 16) (vkFlags (poked :: VkMemoryAllocateFlagsInfo)) *> poke (ptr `plusPtr` 20) (vkDeviceMask (poked :: VkMemoryAllocateFlagsInfo)) -- | VkDeviceGroupRenderPassBeginInfo - Set the initial device mask and -- render areas for a render pass instance data VkDeviceGroupRenderPassBeginInfo = VkDeviceGroupRenderPassBeginInfo { -- No documentation found for Nested "VkDeviceGroupRenderPassBeginInfo" "vkSType" vkSType :: VkStructureType , -- No documentation found for Nested "VkDeviceGroupRenderPassBeginInfo" "vkPNext" vkPNext :: Ptr () , -- No documentation found for Nested "VkDeviceGroupRenderPassBeginInfo" "vkDeviceMask" vkDeviceMask :: Word32 , -- No documentation found for Nested "VkDeviceGroupRenderPassBeginInfo" "vkDeviceRenderAreaCount" vkDeviceRenderAreaCount :: Word32 , -- No documentation found for Nested "VkDeviceGroupRenderPassBeginInfo" "vkPDeviceRenderAreas" vkPDeviceRenderAreas :: Ptr VkRect2D } deriving (Eq, Show) instance Storable VkDeviceGroupRenderPassBeginInfo where sizeOf ~_ = 32 alignment ~_ = 8 peek ptr = VkDeviceGroupRenderPassBeginInfo <$> peek (ptr `plusPtr` 0) <*> peek (ptr `plusPtr` 8) <*> peek (ptr `plusPtr` 16) <*> peek (ptr `plusPtr` 20) <*> peek (ptr `plusPtr` 24) poke ptr poked = poke (ptr `plusPtr` 0) (vkSType (poked :: VkDeviceGroupRenderPassBeginInfo)) *> poke (ptr `plusPtr` 8) (vkPNext (poked :: VkDeviceGroupRenderPassBeginInfo)) *> poke (ptr `plusPtr` 16) (vkDeviceMask (poked :: VkDeviceGroupRenderPassBeginInfo)) *> poke (ptr `plusPtr` 20) (vkDeviceRenderAreaCount (poked :: VkDeviceGroupRenderPassBeginInfo)) *> poke (ptr `plusPtr` 24) (vkPDeviceRenderAreas (poked :: VkDeviceGroupRenderPassBeginInfo)) -- | VkDeviceGroupCommandBufferBeginInfo - Set the initial device mask for a -- command buffer data VkDeviceGroupCommandBufferBeginInfo = VkDeviceGroupCommandBufferBeginInfo { -- No documentation found for Nested "VkDeviceGroupCommandBufferBeginInfo" "vkSType" vkSType :: VkStructureType , -- No documentation found for Nested "VkDeviceGroupCommandBufferBeginInfo" "vkPNext" vkPNext :: Ptr () , -- No documentation found for Nested "VkDeviceGroupCommandBufferBeginInfo" "vkDeviceMask" vkDeviceMask :: Word32 } deriving (Eq, Show) instance Storable VkDeviceGroupCommandBufferBeginInfo where sizeOf ~_ = 24 alignment ~_ = 8 peek ptr = VkDeviceGroupCommandBufferBeginInfo <$> peek (ptr `plusPtr` 0) <*> peek (ptr `plusPtr` 8) <*> peek (ptr `plusPtr` 16) poke ptr poked = poke (ptr `plusPtr` 0) (vkSType (poked :: VkDeviceGroupCommandBufferBeginInfo)) *> poke (ptr `plusPtr` 8) (vkPNext (poked :: VkDeviceGroupCommandBufferBeginInfo)) *> poke (ptr `plusPtr` 16) (vkDeviceMask (poked :: VkDeviceGroupCommandBufferBeginInfo)) -- | VkDeviceGroupSubmitInfo - Structure indicating which physical devices -- execute semaphore operations and command buffers data VkDeviceGroupSubmitInfo = VkDeviceGroupSubmitInfo { -- No documentation found for Nested "VkDeviceGroupSubmitInfo" "vkSType" vkSType :: VkStructureType , -- No documentation found for Nested "VkDeviceGroupSubmitInfo" "vkPNext" vkPNext :: Ptr () , -- No documentation found for Nested "VkDeviceGroupSubmitInfo" "vkWaitSemaphoreCount" vkWaitSemaphoreCount :: Word32 , -- No documentation found for Nested "VkDeviceGroupSubmitInfo" "vkPWaitSemaphoreDeviceIndices" vkPWaitSemaphoreDeviceIndices :: Ptr Word32 , -- No documentation found for Nested "VkDeviceGroupSubmitInfo" "vkCommandBufferCount" vkCommandBufferCount :: Word32 , -- No documentation found for Nested "VkDeviceGroupSubmitInfo" "vkPCommandBufferDeviceMasks" vkPCommandBufferDeviceMasks :: Ptr Word32 , -- No documentation found for Nested "VkDeviceGroupSubmitInfo" "vkSignalSemaphoreCount" vkSignalSemaphoreCount :: Word32 , -- No documentation found for Nested "VkDeviceGroupSubmitInfo" "vkPSignalSemaphoreDeviceIndices" vkPSignalSemaphoreDeviceIndices :: Ptr Word32 } deriving (Eq, Show) instance Storable VkDeviceGroupSubmitInfo where sizeOf ~_ = 64 alignment ~_ = 8 peek ptr = VkDeviceGroupSubmitInfo <$> peek (ptr `plusPtr` 0) <*> peek (ptr `plusPtr` 8) <*> peek (ptr `plusPtr` 16) <*> peek (ptr `plusPtr` 24) <*> peek (ptr `plusPtr` 32) <*> peek (ptr `plusPtr` 40) <*> peek (ptr `plusPtr` 48) <*> peek (ptr `plusPtr` 56) poke ptr poked = poke (ptr `plusPtr` 0) (vkSType (poked :: VkDeviceGroupSubmitInfo)) *> poke (ptr `plusPtr` 8) (vkPNext (poked :: VkDeviceGroupSubmitInfo)) *> poke (ptr `plusPtr` 16) (vkWaitSemaphoreCount (poked :: VkDeviceGroupSubmitInfo)) *> poke (ptr `plusPtr` 24) (vkPWaitSemaphoreDeviceIndices (poked :: VkDeviceGroupSubmitInfo)) *> poke (ptr `plusPtr` 32) (vkCommandBufferCount (poked :: VkDeviceGroupSubmitInfo)) *> poke (ptr `plusPtr` 40) (vkPCommandBufferDeviceMasks (poked :: VkDeviceGroupSubmitInfo)) *> poke (ptr `plusPtr` 48) (vkSignalSemaphoreCount (poked :: VkDeviceGroupSubmitInfo)) *> poke (ptr `plusPtr` 56) (vkPSignalSemaphoreDeviceIndices (poked :: VkDeviceGroupSubmitInfo)) -- | VkDeviceGroupBindSparseInfo - Structure indicating which instances are -- bound data VkDeviceGroupBindSparseInfo = VkDeviceGroupBindSparseInfo { -- No documentation found for Nested "VkDeviceGroupBindSparseInfo" "vkSType" vkSType :: VkStructureType , -- No documentation found for Nested "VkDeviceGroupBindSparseInfo" "vkPNext" vkPNext :: Ptr () , -- No documentation found for Nested "VkDeviceGroupBindSparseInfo" "vkResourceDeviceIndex" vkResourceDeviceIndex :: Word32 , -- No documentation found for Nested "VkDeviceGroupBindSparseInfo" "vkMemoryDeviceIndex" vkMemoryDeviceIndex :: Word32 } deriving (Eq, Show) instance Storable VkDeviceGroupBindSparseInfo where sizeOf ~_ = 24 alignment ~_ = 8 peek ptr = VkDeviceGroupBindSparseInfo <$> peek (ptr `plusPtr` 0) <*> peek (ptr `plusPtr` 8) <*> peek (ptr `plusPtr` 16) <*> peek (ptr `plusPtr` 20) poke ptr poked = poke (ptr `plusPtr` 0) (vkSType (poked :: VkDeviceGroupBindSparseInfo)) *> poke (ptr `plusPtr` 8) (vkPNext (poked :: VkDeviceGroupBindSparseInfo)) *> poke (ptr `plusPtr` 16) (vkResourceDeviceIndex (poked :: VkDeviceGroupBindSparseInfo)) *> poke (ptr `plusPtr` 20) (vkMemoryDeviceIndex (poked :: VkDeviceGroupBindSparseInfo)) -- | VkPeerMemoryFeatureFlags - Bitmask of VkPeerMemoryFeatureFlagBits type VkPeerMemoryFeatureFlags = VkPeerMemoryFeatureFlagBits -- | VkMemoryAllocateFlags - Bitmask of VkMemoryAllocateFlagBits type VkMemoryAllocateFlags = VkMemoryAllocateFlagBits