Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- enumerate :: I s -> IO [P]
- data P
- getProperties :: P -> IO Properties
- data Properties = Properties {}
- getFeatures :: P -> IO Features
- getProperties2ExtensionName :: ExtensionName
- getFeatures2 :: forall (mn :: Maybe Type). ReadChain mn => P -> IO (Features2 mn)
- data Features2 (mn :: Maybe Type) = Features2 {
- features2Next :: M mn
- features2Features :: Features
- getMemoryProperties :: P -> IO MemoryProperties
- data MemoryProperties = MemoryProperties {}
- getQueueFamilyProperties :: P -> IO [(Index, Properties)]
- getFormatProperties :: P -> Format -> IO FormatProperties
- enumerateExtensionProperties :: P -> Maybe LayerName -> IO [ExtensionProperties]
- data ExtensionProperties = ExtensionProperties {}
- newtype ExtensionName = ExtensionName {}
- data ShaderDrawParametersFeatures (mn :: Maybe Type) = ShaderDrawParametersFeatures {}
- maintenance3ExtensionName :: ExtensionName
- newtype Type = Type Word32
- pattern TypeMaxEnum :: Type
- unType :: Type -> Word32
- pattern TypeCpu :: Type
- pattern TypeVirtualGpu :: Type
- pattern TypeDiscreteGpu :: Type
- pattern TypeIntegratedGpu :: Type
- pattern TypeOther :: Type
- data Limits = Limits {
- limitsMaxImageDimension1D :: Word32
- limitsMaxImageDimension2D :: Word32
- limitsMaxImageDimension3D :: Word32
- limitsMaxImageDimensionCube :: Word32
- limitsMaxImageArrayLayers :: Word32
- limitsMaxTexelBufferElements :: Word32
- limitsMaxUniformBufferRange :: Word32
- limitsMaxStorageBufferRange :: Word32
- limitsMaxPushConstantsSize :: Word32
- limitsMaxMemoryAllocationCount :: Word32
- limitsMaxSamplerAllocationCount :: Word32
- limitsBufferImageGranularity :: Size
- limitsSparseAddressSpaceSize :: Size
- limitsMaxBoundDescriptorSets :: Word32
- limitsMaxPerStageDescriptorSamplers :: Word32
- limitsMaxPerStageDescriptorUniformBuffers :: Word32
- limitsMaxPerStageDescriptorStorageBuffers :: Word32
- limitsMaxPerStageDescriptorSampledImages :: Word32
- limitsMaxPerStageDescriptorStorageImages :: Word32
- limitsMaxPerStageDescriptorInputAttachments :: Word32
- limitsMaxPerStageResources :: Word32
- limitsMaxDescriptorSetSamplers :: Word32
- limitsMaxDescriptorSetUniformBuffers :: Word32
- limitsMaxDescriptorSetUniformBuffersDynamic :: Word32
- limitsMaxDescriptorSetStorageBuffers :: Word32
- limitsMaxDescriptorSetStorageBuffersDynamic :: Word32
- limitsMaxDescriptorSetSampledImages :: Word32
- limitsMaxDescriptorSetStorageImages :: Word32
- limitsMaxDescriptorSetInputAttachments :: Word32
- limitsMaxVertexInputAttributes :: Word32
- limitsMaxVertexInputBindings :: Word32
- limitsMaxVertexInputAttributeOffset :: Word32
- limitsMaxVertexInputBindingStride :: Word32
- limitsMaxVertexOutputComponents :: Word32
- limitsMaxTessellationGenerationLevel :: Word32
- limitsMaxTessellationPatchSize :: Word32
- limitsMaxTessellationControlPerVertexInputComponents :: Word32
- limitsMaxTessellationControlPerVertexOutputComponents :: Word32
- limitsMaxTessellationControlPerPatchOutputComponents :: Word32
- limitsMaxTessellationControlTotalOutputComponents :: Word32
- limitsMaxTessellationEvaluationInputComponents :: Word32
- limitsMaxTessellationEvaluationOutputComponents :: Word32
- limitsMaxGeometryShaderInvocations :: Word32
- limitsMaxGeometryInputComponents :: Word32
- limitsMaxGeometryOutputComponents :: Word32
- limitsMaxGeometryOutputVertices :: Word32
- limitsMaxGeometryTotalOutputComponents :: Word32
- limitsMaxFragmentInputComponents :: Word32
- limitsMaxFragmentOutputAttachments :: Word32
- limitsMaxFragmentDualSrcAttachments :: Word32
- limitsMaxFragmentCombinedOutputResources :: Word32
- limitsMaxComputeSharedMemorySize :: Word32
- limitsMaxComputeWorkGroupCount :: LengthL 3 Word32
- limitsMaxComputeWorkGroupInvocations :: Word32
- limitsMaxComputeWorkGroupSize :: LengthL 3 Word32
- limitsSubPixelPrecisionBits :: Word32
- limitsSubTexelPrecisionBits :: Word32
- limitsMipmapPrecisionBits :: Word32
- limitsMaxDrawIndexedIndexValue :: Word32
- limitsMaxDrawIndirectCount :: Word32
- limitsMaxSamplerLodBias :: Float
- limitsMaxSamplerAnisotropy :: Float
- limitsMaxViewports :: Word32
- limitsMaxViewportDimensions :: LengthL 2 Word32
- limitsViewportBoundsRange :: LengthL 2 Float
- limitsViewportSubPixelBits :: Word32
- limitsMinMemoryMapAlignment :: Size
- limitsMinTexelBufferOffsetAlignment :: Size
- limitsMinUniformBufferOffsetAlignment :: Size
- limitsMinStorageBufferOffsetAlignment :: Size
- limitsMinTexelOffset :: Int32
- limitsMaxTexelOffset :: Word32
- limitsMinTexelGatherOffset :: Int32
- limitsMaxTexelGatherOffset :: Word32
- limitsMinInterpolationOffset :: Float
- limitsMaxInterpolationOffset :: Float
- limitsSubPixelInterpolationOffsetBits :: Word32
- limitsMaxFramebufferWidth :: Word32
- limitsMaxFramebufferHeight :: Word32
- limitsMaxFramebufferLayers :: Word32
- limitsFramebufferColorSampleCounts :: CountFlags
- limitsFramebufferDepthSampleCounts :: CountFlags
- limitsFramebufferStencilSampleCounts :: CountFlags
- limitsFramebufferNoAttachmentsSampleCounts :: CountFlags
- limitsMaxColorAttachments :: Word32
- limitsSampledImageColorSampleCounts :: CountFlags
- limitsSampledImageIntegerSampleCounts :: CountFlags
- limitsSampledImageDepthSampleCounts :: CountFlags
- limitsSampledImageStencilSampleCounts :: CountFlags
- limitsStorageImageSampleCounts :: CountFlags
- limitsMaxSampleMaskWords :: Word32
- limitsTimestampComputeAndGraphics :: Bool
- limitsTimestampPeriod :: Float
- limitsMaxClipDistances :: Word32
- limitsMaxCullDistances :: Word32
- limitsMaxCombinedClipAndCullDistances :: Word32
- limitsDiscreteQueuePriorities :: Word32
- limitsPointSizeRange :: LengthL 2 Float
- limitsLineWidthRange :: LengthL 2 Float
- limitsPointSizeGranularity :: Float
- limitsLineWidthGranularity :: Float
- limitsStrictLines :: Bool
- limitsStandardSampleLocations :: Bool
- limitsOptimalBufferCopyOffsetAlignment :: Size
- limitsOptimalBufferCopyRowPitchAlignment :: Size
- limitsNonCoherentAtomSize :: Size
- data Features = Features {
- featuresRobustBufferAccess :: Bool
- featuresFullDrawIndexUint32 :: Bool
- featuresImageCubeArray :: Bool
- featuresIndependentBlend :: Bool
- featuresGeometryShader :: Bool
- featuresTessellationShader :: Bool
- featuresSampleRateShading :: Bool
- featuresDualSrcBlend :: Bool
- featuresLogicOp :: Bool
- featuresMultiDrawIndirect :: Bool
- featuresDrawIndirectFirstInstance :: Bool
- featuresDepthClamp :: Bool
- featuresDepthBiasClamp :: Bool
- featuresFillModeNonSolid :: Bool
- featuresDepthBounds :: Bool
- featuresWideLines :: Bool
- featuresLargePoints :: Bool
- featuresAlphaToOne :: Bool
- featuresMultiViewport :: Bool
- featuresSamplerAnisotropy :: Bool
- featuresTextureCompressionETC2 :: Bool
- featuresTextureCompressionASTC_LDR :: Bool
- featuresTextureCompressionBC :: Bool
- featuresOcclusionQueryPrecise :: Bool
- featuresPipelineStatisticsQuery :: Bool
- featuresVertexPipelineStoresAndAtomics :: Bool
- featuresFragmentStoresAndAtomics :: Bool
- featuresShaderTessellationAndGeometryPointSize :: Bool
- featuresShaderImageGatherExtended :: Bool
- featuresShaderStorageImageExtendedFormats :: Bool
- featuresShaderStorageImageMultisample :: Bool
- featuresShaderStorageImageReadWithoutFormat :: Bool
- featuresShaderStorageImageWriteWithoutFormat :: Bool
- featuresShaderUniformBufferArrayDynamicIndexing :: Bool
- featuresShaderSampledImageArrayDynamicIndexing :: Bool
- featuresShaderStorageBufferArrayDynamicIndexing :: Bool
- featuresShaderStorageImageArrayDynamicIndexing :: Bool
- featuresShaderClipDistance :: Bool
- featuresShaderCullDistance :: Bool
- featuresShaderFloat64 :: Bool
- featuresShaderInt64 :: Bool
- featuresShaderInt16 :: Bool
- featuresShaderResourceResidency :: Bool
- featuresShaderResourceMinLod :: Bool
- featuresSparseBinding :: Bool
- featuresSparseResidencyBuffer :: Bool
- featuresSparseResidencyImage2D :: Bool
- featuresSparseResidencyImage3D :: Bool
- featuresSparseResidency2Samples :: Bool
- featuresSparseResidency4Samples :: Bool
- featuresSparseResidency8Samples :: Bool
- featuresSparseResidency16Samples :: Bool
- featuresSparseResidencyAliased :: Bool
- featuresVariableMultisampleRate :: Bool
- featuresInheritedQueries :: Bool
- data Vulkan12Features (mn :: Maybe Type) = Vulkan12Features {
- vulkan12FeaturesNext :: M mn
- vulkan12FeaturesSamplerMirrorClampToEdge :: Bool
- vulkan12FeaturesDrawIndirectCount :: Bool
- vulkan12FeaturesStorageBuffer8BitAccess :: Bool
- vulkan12FeaturesUniformAndStorageBuffer8BitAccess :: Bool
- vulkan12FeaturesStoragePushConstant8 :: Bool
- vulkan12FeaturesShaderBufferInt64Atomics :: Bool
- vulkan12FeaturesShaderSharedInt64Atomics :: Bool
- vulkan12FeaturesShaderFloat16 :: Bool
- vulkan12FeaturesShaderInt8 :: Bool
- vulkan12FeaturesDescriptorIndexing :: Bool
- vulkan12FeaturesShaderInputAttachmentArrayDynamicIndexing :: Bool
- vulkan12FeaturesShaderUniformTexelBufferArrayDynamicIndexing :: Bool
- vulkan12FeaturesShaderStorageTexelBufferArrayDynamicIndexing :: Bool
- vulkan12FeaturesShaderUniformBufferArrayNonUniformIndexing :: Bool
- vulkan12FeaturesShaderSampledImageArrayNonUniformIndexing :: Bool
- vulkan12FeaturesShaderStorageBufferArrayNonUniformIndexing :: Bool
- vulkan12FeaturesShaderStorageImageArrayNonUniformIndexing :: Bool
- vulkan12FeaturesShaderInputAttachmentArrayNonUniformIndexing :: Bool
- vulkan12FeaturesShaderUniformTexelBufferArrayNonUniformIndexing :: Bool
- vulkan12FeaturesShaderStorageTexelBufferArrayNonUniformIndexing :: Bool
- vulkan12FeaturesDescriptorBindingUniformBufferUpdateAfterBind :: Bool
- vulkan12FeaturesDescriptorBindingSampledImageUpdateAfterBind :: Bool
- vulkan12FeaturesDescriptorBindingStorageImageUpdateAfterBind :: Bool
- vulkan12FeaturesDescriptorBindingStorageBufferUpdateAfterBind :: Bool
- vulkan12FeaturesDescriptorBindingUniformTexelBufferUpdateAfterBind :: Bool
- vulkan12FeaturesDescriptorBindingStorageTexelBufferUpdateAfterBind :: Bool
- vulkan12FeaturesDescriptorBindingUpdateUnusedWhilePending :: Bool
- vulkan12FeaturesDescriptorBindingPartiallyBound :: Bool
- vulkan12FeaturesDescriptorBindingVariableDescriptorCount :: Bool
- vulkan12FeaturesRuntimeDescriptorArray :: Bool
- vulkan12FeaturesSamplerFilterMinmax :: Bool
- vulkan12FeaturesScalarBlockLayout :: Bool
- vulkan12FeaturesImagelessFramebuffer :: Bool
- vulkan12FeaturesUniformBufferStandardLayout :: Bool
- vulkan12FeaturesShaderSubgroupExtendedTypes :: Bool
- vulkan12FeaturesSeparateDepthStencilLayouts :: Bool
- vulkan12FeaturesHostQueryReset :: Bool
- vulkan12FeaturesTimelineSemaphore :: Bool
- vulkan12FeaturesBufferDeviceAddress :: Bool
- vulkan12FeaturesBufferDeviceAddressCaptureReplay :: Bool
- vulkan12FeaturesBufferDeviceAddressMultiDevice :: Bool
- vulkan12FeaturesVulkanMemoryModel :: Bool
- vulkan12FeaturesVulkanMemoryModelDeviceScope :: Bool
- vulkan12FeaturesVulkanMemoryModelAvailabilityVisibilityChains :: Bool
- vulkan12FeaturesShaderOutputViewportIndex :: Bool
- vulkan12FeaturesShaderOutputLayer :: Bool
- vulkan12FeaturesSubgroupBroadcastDynamicId :: Bool
- data Vulkan12FeaturesNoNext = Vulkan12FeaturesNoNext {
- vulkan12FeaturesNoNextSamplerMirrorClampToEdge :: Bool
- vulkan12FeaturesNoNextDrawIndirectCount :: Bool
- vulkan12FeaturesNoNextStorageBuffer8BitAccess :: Bool
- vulkan12FeaturesNoNextUniformAndStorageBuffer8BitAccess :: Bool
- vulkan12FeaturesNoNextStoragePushConstant8 :: Bool
- vulkan12FeaturesNoNextShaderBufferInt64Atomics :: Bool
- vulkan12FeaturesNoNextShaderSharedInt64Atomics :: Bool
- vulkan12FeaturesNoNextShaderFloat16 :: Bool
- vulkan12FeaturesNoNextShaderInt8 :: Bool
- vulkan12FeaturesNoNextDescriptorIndexing :: Bool
- vulkan12FeaturesNoNextShaderInputAttachmentArrayDynamicIndexing :: Bool
- vulkan12FeaturesNoNextShaderUniformTexelBufferArrayDynamicIndexing :: Bool
- vulkan12FeaturesNoNextShaderStorageTexelBufferArrayDynamicIndexing :: Bool
- vulkan12FeaturesNoNextShaderUniformBufferArrayNonUniformIndexing :: Bool
- vulkan12FeaturesNoNextShaderSampledImageArrayNonUniformIndexing :: Bool
- vulkan12FeaturesNoNextShaderStorageBufferArrayNonUniformIndexing :: Bool
- vulkan12FeaturesNoNextShaderStorageImageArrayNonUniformIndexing :: Bool
- vulkan12FeaturesNoNextShaderInputAttachmentArrayNonUniformIndexing :: Bool
- vulkan12FeaturesNoNextShaderUniformTexelBufferArrayNonUniformIndexing :: Bool
- vulkan12FeaturesNoNextShaderStorageTexelBufferArrayNonUniformIndexing :: Bool
- vulkan12FeaturesNoNextDescriptorBindingUniformBufferUpdateAfterBind :: Bool
- vulkan12FeaturesNoNextDescriptorBindingSampledImageUpdateAfterBind :: Bool
- vulkan12FeaturesNoNextDescriptorBindingStorageImageUpdateAfterBind :: Bool
- vulkan12FeaturesNoNextDescriptorBindingStorageBufferUpdateAfterBind :: Bool
- vulkan12FeaturesNoNextDescriptorBindingUniformTexelBufferUpdateAfterBind :: Bool
- vulkan12FeaturesNoNextDescriptorBindingStorageTexelBufferUpdateAfterBind :: Bool
- vulkan12FeaturesNoNextDescriptorBindingUpdateUnusedWhilePending :: Bool
- vulkan12FeaturesNoNextDescriptorBindingPartiallyBound :: Bool
- vulkan12FeaturesNoNextDescriptorBindingVariableDescriptorCount :: Bool
- vulkan12FeaturesNoNextRuntimeDescriptorArray :: Bool
- vulkan12FeaturesNoNextSamplerFilterMinmax :: Bool
- vulkan12FeaturesNoNextScalarBlockLayout :: Bool
- vulkan12FeaturesNoNextImagelessFramebuffer :: Bool
- vulkan12FeaturesNoNextUniformBufferStandardLayout :: Bool
- vulkan12FeaturesNoNextShaderSubgroupExtendedTypes :: Bool
- vulkan12FeaturesNoNextSeparateDepthStencilLayouts :: Bool
- vulkan12FeaturesNoNextHostQueryReset :: Bool
- vulkan12FeaturesNoNextTimelineSemaphore :: Bool
- vulkan12FeaturesNoNextBufferDeviceAddress :: Bool
- vulkan12FeaturesNoNextBufferDeviceAddressCaptureReplay :: Bool
- vulkan12FeaturesNoNextBufferDeviceAddressMultiDevice :: Bool
- vulkan12FeaturesNoNextVulkanMemoryModel :: Bool
- vulkan12FeaturesNoNextVulkanMemoryModelDeviceScope :: Bool
- vulkan12FeaturesNoNextVulkanMemoryModelAvailabilityVisibilityChains :: Bool
- vulkan12FeaturesNoNextShaderOutputViewportIndex :: Bool
- vulkan12FeaturesNoNextShaderOutputLayer :: Bool
- vulkan12FeaturesNoNextSubgroupBroadcastDynamicId :: Bool
- vulkan12FeaturesZero :: forall (mn :: Maybe Type). M mn -> Vulkan12Features mn
- data Vulkan13Features (mn :: Maybe Type) = Vulkan13Features {
- vulkan13FeaturesNext :: M mn
- vulkan13FeaturesRobustImageAccess :: Bool
- vulkan13FeaturesInlineUniformBlock :: Bool
- vulkan13FeaturesDescriptorBindingInlineUniformBlockUpdateAfterBind :: Bool
- vulkan13FeaturesPipelineCreationCacheControl :: Bool
- vulkan13FeaturesPrivateData :: Bool
- vulkan13FeaturesShaderDemoteToHelperInvocation :: Bool
- vulkan13FeaturesShaderTerminateInvocation :: Bool
- vulkan13FeaturesSubgroupSizeControl :: Bool
- vulkan13FeaturesComputeFullSubgroups :: Bool
- vulkan13FeaturesSynchronization2 :: Bool
- vulkan13FeaturesTextureCompressionASTC_HDR :: Bool
- vulkan13FeaturesShaderZeroInitializeWorkgroupMemory :: Bool
- vulkan13FeaturesDynamicRendering :: Bool
- vulkan13FeaturesShaderIntegerDotProduct :: Bool
- vulkan13FeaturesMaintenance4 :: Bool
- data Vulkan13FeaturesNoNext = Vulkan13FeaturesNoNext {
- vulkan13FeaturesNoNextRobustImageAccess :: Bool
- vulkan13FeaturesNoNextInlineUniformBlock :: Bool
- vulkan13FeaturesNoNextDescriptorBindingInlineUniformBlockUpdateAfterBind :: Bool
- vulkan13FeaturesNoNextPipelineCreationCacheControl :: Bool
- vulkan13FeaturesNoNextPrivateData :: Bool
- vulkan13FeaturesNoNextShaderDemoteToHelperInvocation :: Bool
- vulkan13FeaturesNoNextShaderTerminateInvocation :: Bool
- vulkan13FeaturesNoNextSubgroupSizeControl :: Bool
- vulkan13FeaturesNoNextComputeFullSubgroups :: Bool
- vulkan13FeaturesNoNextSynchronization2 :: Bool
- vulkan13FeaturesNoNextTextureCompressionASTC_HDR :: Bool
- vulkan13FeaturesNoNextShaderZeroInitializeWorkgroupMemory :: Bool
- vulkan13FeaturesNoNextDynamicRendering :: Bool
- vulkan13FeaturesNoNextShaderIntegerDotProduct :: Bool
- vulkan13FeaturesNoNextMaintenance4 :: Bool
- vulkan13FeaturesZero :: forall (mn :: Maybe Type). M mn -> Vulkan13Features mn
- data DescriptorIndexingFeatures (mn :: Maybe Type) = DescriptorIndexingFeatures {
- descriptorIndexingFeaturesNext :: M mn
- descriptorIndexingFeaturesShaderInputAttachmentArrayDynamicIndexing :: Bool
- descriptorIndexingFeaturesShaderUniformTexelBufferArrayDynamicIndexing :: Bool
- descriptorIndexingFeaturesShaderStorageTexelBufferArrayDynamicIndexing :: Bool
- descriptorIndexingFeaturesShaderUniformBufferArrayNonUniformIndexing :: Bool
- descriptorIndexingFeaturesShaderSampledImageArrayNonUniformIndexing :: Bool
- descriptorIndexingFeaturesShaderStorageBufferArrayNonUniformIndexing :: Bool
- descriptorIndexingFeaturesShaderStorageImageArrayNonUniformIndexing :: Bool
- descriptorIndexingFeaturesShaderInputAttachmentArrayNonUniformIndexing :: Bool
- descriptorIndexingFeaturesShaderUniformTexelBufferArrayNonUniformIndexing :: Bool
- descriptorIndexingFeaturesShaderStorageTexelBufferArrayNonUniformIndexing :: Bool
- descriptorIndexingFeaturesDescriptorBindingUniformBufferUpdateAfterBind :: Bool
- descriptorIndexingFeaturesDescriptorBindingSampledImageUpdateAfterBind :: Bool
- descriptorIndexingFeaturesDescriptorBindingStorageImageUpdateAfterBind :: Bool
- descriptorIndexingFeaturesDescriptorBindingStorageBufferUpdateAfterBind :: Bool
- descriptorIndexingFeaturesDescriptorBindingUniformTexelBufferUpdateAfterBind :: Bool
- descriptorIndexingFeaturesDescriptorBindingStorageTexelBufferUpdateAfterBind :: Bool
- descriptorIndexingFeaturesDescriptorBindingUpdateUnusedWhilePending :: Bool
- descriptorIndexingFeaturesDescriptorBindingPartiallyBound :: Bool
- descriptorIndexingFeaturesDescriptorBindingVariableDescriptorCount :: Bool
- descriptorIndexingFeaturesRuntimeDescriptorArray :: Bool
- data DescriptorIndexingFeaturesNoNext = DescriptorIndexingFeaturesNoNext {
- descriptorIndexingFeaturesNoNextShaderInputAttachmentArrayDynamicIndexing :: Bool
- descriptorIndexingFeaturesNoNextShaderUniformTexelBufferArrayDynamicIndexing :: Bool
- descriptorIndexingFeaturesNoNextShaderStorageTexelBufferArrayDynamicIndexing :: Bool
- descriptorIndexingFeaturesNoNextShaderUniformBufferArrayNonUniformIndexing :: Bool
- descriptorIndexingFeaturesNoNextShaderSampledImageArrayNonUniformIndexing :: Bool
- descriptorIndexingFeaturesNoNextShaderStorageBufferArrayNonUniformIndexing :: Bool
- descriptorIndexingFeaturesNoNextShaderStorageImageArrayNonUniformIndexing :: Bool
- descriptorIndexingFeaturesNoNextShaderInputAttachmentArrayNonUniformIndexing :: Bool
- descriptorIndexingFeaturesNoNextShaderUniformTexelBufferArrayNonUniformIndexing :: Bool
- descriptorIndexingFeaturesNoNextShaderStorageTexelBufferArrayNonUniformIndexing :: Bool
- descriptorIndexingFeaturesNoNextDescriptorBindingUniformBufferUpdateAfterBind :: Bool
- descriptorIndexingFeaturesNoNextDescriptorBindingSampledImageUpdateAfterBind :: Bool
- descriptorIndexingFeaturesNoNextDescriptorBindingStorageImageUpdateAfterBind :: Bool
- descriptorIndexingFeaturesNoNextDescriptorBindingStorageBufferUpdateAfterBind :: Bool
- descriptorIndexingFeaturesNoNextDescriptorBindingUniformTexelBufferUpdateAfterBind :: Bool
- descriptorIndexingFeaturesNoNextDescriptorBindingStorageTexelBufferUpdateAfterBind :: Bool
- descriptorIndexingFeaturesNoNextDescriptorBindingUpdateUnusedWhilePending :: Bool
- descriptorIndexingFeaturesNoNextDescriptorBindingPartiallyBound :: Bool
- descriptorIndexingFeaturesNoNextDescriptorBindingVariableDescriptorCount :: Bool
- descriptorIndexingFeaturesNoNextRuntimeDescriptorArray :: Bool
- descriptorIndexingFeaturesZero :: forall (mn :: Maybe Type). M mn -> DescriptorIndexingFeatures mn
ENUMERATE
PHYSICAL DEVICE PROPERTIES AND FEATURES
getProperties :: P -> IO Properties #
data Properties #
Properties | |
|
Instances
Show Properties | |
Defined in Gpu.Vulkan.PhysicalDevice.Middle.Internal showsPrec :: Int -> Properties -> ShowS # show :: Properties -> String # showList :: [Properties] -> ShowS # |
getFeatures :: P -> IO Features #
Get Properties 2
data Features2 (mn :: Maybe Type) #
Features2 | |
|
OTHER PROPERTIES
getMemoryProperties :: P -> IO MemoryProperties #
data MemoryProperties #
Instances
Show MemoryProperties | |
Defined in Gpu.Vulkan.PhysicalDevice.Middle.Internal showsPrec :: Int -> MemoryProperties -> ShowS # show :: MemoryProperties -> String # showList :: [MemoryProperties] -> ShowS # |
getQueueFamilyProperties :: P -> IO [(Index, Properties)] #
getFormatProperties :: P -> Format -> IO FormatProperties #
enumerateExtensionProperties :: P -> Maybe LayerName -> IO [ExtensionProperties] Source #
data ExtensionProperties Source #
Instances
Show ExtensionProperties Source # | |
Defined in Gpu.Vulkan.PhysicalDevice showsPrec :: Int -> ExtensionProperties -> ShowS # show :: ExtensionProperties -> String # showList :: [ExtensionProperties] -> ShowS # |
newtype ExtensionName Source #
Instances
Show ExtensionName Source # | |
Defined in Gpu.Vulkan.PhysicalDevice showsPrec :: Int -> ExtensionName -> ShowS # show :: ExtensionName -> String # showList :: [ExtensionName] -> ShowS # | |
Eq ExtensionName Source # | |
Defined in Gpu.Vulkan.PhysicalDevice (==) :: ExtensionName -> ExtensionName -> Bool # (/=) :: ExtensionName -> ExtensionName -> Bool # |
OTHER FEATURES
data ShaderDrawParametersFeatures (mn :: Maybe Type) #
Instances
Show (M mn) => Show (ShaderDrawParametersFeatures mn) | |
Defined in Gpu.Vulkan.PhysicalDevice.Middle.Internal showsPrec :: Int -> ShaderDrawParametersFeatures mn -> ShowS # show :: ShaderDrawParametersFeatures mn -> String # showList :: [ShaderDrawParametersFeatures mn] -> ShowS # | |
WithPoked (M mn) => WithPoked (ShaderDrawParametersFeatures mn) | |
Defined in Gpu.Vulkan.PhysicalDevice.Middle.Internal withPoked' :: ShaderDrawParametersFeatures mn -> (forall s. PtrS s (ShaderDrawParametersFeatures mn) -> IO b) -> IO b # |
EXTENSIONS
ENUM AND STRUCT
pattern TypeMaxEnum :: Type #
pattern TypeVirtualGpu :: Type #
pattern TypeDiscreteGpu :: Type #
pattern TypeIntegratedGpu :: Type #
data Vulkan12Features (mn :: Maybe Type) #
Instances
Nextable Vulkan12Features | |
Defined in Gpu.Vulkan.PhysicalDevice.Struct nextableSize :: Int # nextableType :: StructureType # nextPtr :: Ptr () -> IO (Ptr ()) # createNextable :: forall (mn' :: Maybe Type). Ptr () -> M mn' -> IO (Vulkan12Features mn') # | |
Show (M mn) => Show (Vulkan12Features mn) | |
Defined in Gpu.Vulkan.PhysicalDevice.Struct showsPrec :: Int -> Vulkan12Features mn -> ShowS # show :: Vulkan12Features mn -> String # showList :: [Vulkan12Features mn] -> ShowS # | |
WithPoked (M mn) => WithPoked (Vulkan12Features mn) | |
Defined in Gpu.Vulkan.PhysicalDevice.Struct withPoked' :: Vulkan12Features mn -> (forall s. PtrS s (Vulkan12Features mn) -> IO b) -> IO b # |
data Vulkan12FeaturesNoNext #
Instances
Show Vulkan12FeaturesNoNext | |
Defined in Gpu.Vulkan.PhysicalDevice.Struct showsPrec :: Int -> Vulkan12FeaturesNoNext -> ShowS # show :: Vulkan12FeaturesNoNext -> String # showList :: [Vulkan12FeaturesNoNext] -> ShowS # | |
Typeable Vulkan12FeaturesNoNext | |
Defined in Gpu.Vulkan.PhysicalDevice.Struct | |
Peek Vulkan12FeaturesNoNext | |
Defined in Gpu.Vulkan.PhysicalDevice.Struct | |
Sizable Vulkan12FeaturesNoNext | |
Defined in Gpu.Vulkan.PhysicalDevice.Struct |
vulkan12FeaturesZero :: forall (mn :: Maybe Type). M mn -> Vulkan12Features mn #
data Vulkan13Features (mn :: Maybe Type) #
Instances
Nextable Vulkan13Features | |
Defined in Gpu.Vulkan.PhysicalDevice.Struct nextableSize :: Int # nextableType :: StructureType # nextPtr :: Ptr () -> IO (Ptr ()) # createNextable :: forall (mn' :: Maybe Type). Ptr () -> M mn' -> IO (Vulkan13Features mn') # | |
Show (M mn) => Show (Vulkan13Features mn) | |
Defined in Gpu.Vulkan.PhysicalDevice.Struct showsPrec :: Int -> Vulkan13Features mn -> ShowS # show :: Vulkan13Features mn -> String # showList :: [Vulkan13Features mn] -> ShowS # | |
WithPoked (M mn) => WithPoked (Vulkan13Features mn) | |
Defined in Gpu.Vulkan.PhysicalDevice.Struct withPoked' :: Vulkan13Features mn -> (forall s. PtrS s (Vulkan13Features mn) -> IO b) -> IO b # |
data Vulkan13FeaturesNoNext #
Instances
Show Vulkan13FeaturesNoNext | |
Defined in Gpu.Vulkan.PhysicalDevice.Struct showsPrec :: Int -> Vulkan13FeaturesNoNext -> ShowS # show :: Vulkan13FeaturesNoNext -> String # showList :: [Vulkan13FeaturesNoNext] -> ShowS # | |
Typeable Vulkan13FeaturesNoNext | |
Defined in Gpu.Vulkan.PhysicalDevice.Struct | |
Peek Vulkan13FeaturesNoNext | |
Defined in Gpu.Vulkan.PhysicalDevice.Struct | |
Sizable Vulkan13FeaturesNoNext | |
Defined in Gpu.Vulkan.PhysicalDevice.Struct |
vulkan13FeaturesZero :: forall (mn :: Maybe Type). M mn -> Vulkan13Features mn #
data DescriptorIndexingFeatures (mn :: Maybe Type) #
Instances
Nextable DescriptorIndexingFeatures | |
Defined in Gpu.Vulkan.PhysicalDevice.Struct nextableSize :: Int # nextableType :: StructureType # nextPtr :: Ptr () -> IO (Ptr ()) # createNextable :: forall (mn' :: Maybe Type). Ptr () -> M mn' -> IO (DescriptorIndexingFeatures mn') # | |
Show (M mn) => Show (DescriptorIndexingFeatures mn) | |
Defined in Gpu.Vulkan.PhysicalDevice.Struct showsPrec :: Int -> DescriptorIndexingFeatures mn -> ShowS # show :: DescriptorIndexingFeatures mn -> String # showList :: [DescriptorIndexingFeatures mn] -> ShowS # | |
WithPoked (M mn) => WithPoked (DescriptorIndexingFeatures mn) | |
Defined in Gpu.Vulkan.PhysicalDevice.Struct withPoked' :: DescriptorIndexingFeatures mn -> (forall s. PtrS s (DescriptorIndexingFeatures mn) -> IO b) -> IO b # |
data DescriptorIndexingFeaturesNoNext #
Instances
descriptorIndexingFeaturesZero :: forall (mn :: Maybe Type). M mn -> DescriptorIndexingFeatures mn #