Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- enumerate :: I -> Ptr Word32 -> Ptr P -> IO Int32
- type P = Ptr PTag
- getProperties :: P -> Ptr Properties -> IO ()
- data Properties
- pattern Properties :: Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Text -> ListUint8T -> Limits -> SparseProperties -> Properties
- propertiesApiVersion :: Properties -> Word32
- propertiesDriverVersion :: Properties -> Word32
- propertiesVendorId :: Properties -> Word32
- propertiesDeviceId :: Properties -> Word32
- propertiesDeviceType :: Properties -> Word32
- propertiesDeviceName :: Properties -> Text
- propertiesPipelineCacheUuid :: Properties -> ListUint8T
- propertiesLimits :: Properties -> Limits
- propertiesSparseProperties :: Properties -> SparseProperties
- data SparseProperties
- pattern SparseProperties :: Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> SparseProperties
- sparsePropertiesResidencyStandard2DBlockShape :: SparseProperties -> Word32
- sparsePropertiesResidencyStandard2DMultisampleBlockShape :: SparseProperties -> Word32
- sparsePropertiesResidencyStandard3DBlockShape :: SparseProperties -> Word32
- sparsePropertiesResidencyAlignedMipSize :: SparseProperties -> Word32
- sparsePropertiesResidencyNonResidentStrict :: SparseProperties -> Word32
- enumerateExtensionProperties :: P -> CString -> Ptr Word32 -> Ptr ExtensionProperties -> IO Int32
- getQueueFamilyProperties :: P -> Ptr Word32 -> Ptr Properties -> IO ()
- getMemoryProperties :: P -> Ptr MemoryProperties -> IO ()
- data MemoryProperties
- pattern MemoryProperties :: Word32 -> ListMType -> Word32 -> ListHeap -> MemoryProperties
- memoryPropertiesMemoryTypeCount :: MemoryProperties -> Word32
- memoryPropertiesMemoryTypes :: MemoryProperties -> ListMType
- memoryPropertiesMemoryHeapCount :: MemoryProperties -> Word32
- memoryPropertiesMemoryHeaps :: MemoryProperties -> ListHeap
- getFormatProperties :: P -> Word32 -> Ptr FormatProperties -> IO ()
- getFeatures :: P -> Ptr Features -> IO ()
- data Features
- pattern Features :: Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Features
- getClearedFeatures :: IO Features
- getFeatures2 :: P -> Ptr Features2 -> IO ()
- data Features2
- pattern Features2 :: () -> PtrVoid -> Features -> Features2
- features2SType :: Features2 -> ()
- features2PNext :: Features2 -> PtrVoid
- features2Features :: Features2 -> Features
- data Vulkan12Features
- pattern Vulkan12Features :: () -> PtrVoid -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Vulkan12Features
- getClearedVulkan12Features :: IO Vulkan12Features
- data Vulkan13Features
- pattern Vulkan13Features :: () -> PtrVoid -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Vulkan13Features
- getClearedVulkan13Features :: IO Vulkan13Features
- data DescriptorIndexingFeatures
- pattern DescriptorIndexingFeatures :: () -> PtrVoid -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> DescriptorIndexingFeatures
- getClearedDescriptorIndexingFeatures :: IO DescriptorIndexingFeatures
- data ShaderDrawParametersFeatures
- pattern ShaderDrawParametersFeatures :: () -> PtrVoid -> Word32 -> ShaderDrawParametersFeatures
- shaderDrawParametersFeaturesSType :: ShaderDrawParametersFeatures -> ()
- shaderDrawParametersFeaturesPNext :: ShaderDrawParametersFeatures -> PtrVoid
- shaderDrawParametersFeaturesShaderDrawParameters :: ShaderDrawParametersFeatures -> Word32
ENUMERATE
PROPERTIES
getProperties :: P -> Ptr Properties -> IO () Source #
data Properties Source #
Instances
Storable Properties Source # | |
Defined in Gpu.Vulkan.PhysicalDevice.Core sizeOf :: Properties -> Int # alignment :: Properties -> Int # peekElemOff :: Ptr Properties -> Int -> IO Properties # pokeElemOff :: Ptr Properties -> Int -> Properties -> IO () # peekByteOff :: Ptr b -> Int -> IO Properties # pokeByteOff :: Ptr b -> Int -> Properties -> IO () # peek :: Ptr Properties -> IO Properties # poke :: Ptr Properties -> Properties -> IO () # | |
Show Properties Source # | |
Defined in Gpu.Vulkan.PhysicalDevice.Core showsPrec :: Int -> Properties -> ShowS # show :: Properties -> String # showList :: [Properties] -> ShowS # |
pattern Properties :: Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Text -> ListUint8T -> Limits -> SparseProperties -> Properties Source #
propertiesLimits :: Properties -> Limits Source #
SparseProperties
data SparseProperties Source #
Instances
Storable SparseProperties Source # | |
Defined in Gpu.Vulkan.PhysicalDevice.Core sizeOf :: SparseProperties -> Int # alignment :: SparseProperties -> Int # peekElemOff :: Ptr SparseProperties -> Int -> IO SparseProperties # pokeElemOff :: Ptr SparseProperties -> Int -> SparseProperties -> IO () # peekByteOff :: Ptr b -> Int -> IO SparseProperties # pokeByteOff :: Ptr b -> Int -> SparseProperties -> IO () # peek :: Ptr SparseProperties -> IO SparseProperties # poke :: Ptr SparseProperties -> SparseProperties -> IO () # | |
Show SparseProperties Source # | |
Defined in Gpu.Vulkan.PhysicalDevice.Core showsPrec :: Int -> SparseProperties -> ShowS # show :: SparseProperties -> String # showList :: [SparseProperties] -> ShowS # |
pattern SparseProperties :: Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> SparseProperties Source #
ExtensionProperties
enumerateExtensionProperties :: P -> CString -> Ptr Word32 -> Ptr ExtensionProperties -> IO Int32 Source #
QqueueFamilyProperties
getQueueFamilyProperties :: P -> Ptr Word32 -> Ptr Properties -> IO () Source #
MemoryProperties
getMemoryProperties :: P -> Ptr MemoryProperties -> IO () Source #
data MemoryProperties Source #
Instances
Storable MemoryProperties Source # | |
Defined in Gpu.Vulkan.PhysicalDevice.Core sizeOf :: MemoryProperties -> Int # alignment :: MemoryProperties -> Int # peekElemOff :: Ptr MemoryProperties -> Int -> IO MemoryProperties # pokeElemOff :: Ptr MemoryProperties -> Int -> MemoryProperties -> IO () # peekByteOff :: Ptr b -> Int -> IO MemoryProperties # pokeByteOff :: Ptr b -> Int -> MemoryProperties -> IO () # peek :: Ptr MemoryProperties -> IO MemoryProperties # poke :: Ptr MemoryProperties -> MemoryProperties -> IO () # | |
Show MemoryProperties Source # | |
Defined in Gpu.Vulkan.PhysicalDevice.Core showsPrec :: Int -> MemoryProperties -> ShowS # show :: MemoryProperties -> String # showList :: [MemoryProperties] -> ShowS # |
pattern MemoryProperties :: Word32 -> ListMType -> Word32 -> ListHeap -> MemoryProperties Source #
FormatProperties
getFormatProperties :: P -> Word32 -> Ptr FormatProperties -> IO () Source #
FEATURES
Get Features
Instances
Storable Features Source # | |
Defined in Gpu.Vulkan.PhysicalDevice.Struct.Core | |
Show Features Source # | |
pattern Features :: Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Features Source #
Get Features 2
Instances
Storable Features2 Source # | |
Defined in Gpu.Vulkan.PhysicalDevice.Core | |
Show Features2 Source # | |
features2SType :: Features2 -> () Source #
features2PNext :: Features2 -> PtrVoid Source #
data Vulkan12Features Source #
Instances
Storable Vulkan12Features Source # | |
Defined in Gpu.Vulkan.PhysicalDevice.Struct.Core sizeOf :: Vulkan12Features -> Int # alignment :: Vulkan12Features -> Int # peekElemOff :: Ptr Vulkan12Features -> Int -> IO Vulkan12Features # pokeElemOff :: Ptr Vulkan12Features -> Int -> Vulkan12Features -> IO () # peekByteOff :: Ptr b -> Int -> IO Vulkan12Features # pokeByteOff :: Ptr b -> Int -> Vulkan12Features -> IO () # peek :: Ptr Vulkan12Features -> IO Vulkan12Features # poke :: Ptr Vulkan12Features -> Vulkan12Features -> IO () # | |
Show Vulkan12Features Source # | |
Defined in Gpu.Vulkan.PhysicalDevice.Struct.Core showsPrec :: Int -> Vulkan12Features -> ShowS # show :: Vulkan12Features -> String # showList :: [Vulkan12Features] -> ShowS # |
pattern Vulkan12Features :: () -> PtrVoid -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Vulkan12Features Source #
data Vulkan13Features Source #
Instances
Storable Vulkan13Features Source # | |
Defined in Gpu.Vulkan.PhysicalDevice.Struct.Core sizeOf :: Vulkan13Features -> Int # alignment :: Vulkan13Features -> Int # peekElemOff :: Ptr Vulkan13Features -> Int -> IO Vulkan13Features # pokeElemOff :: Ptr Vulkan13Features -> Int -> Vulkan13Features -> IO () # peekByteOff :: Ptr b -> Int -> IO Vulkan13Features # pokeByteOff :: Ptr b -> Int -> Vulkan13Features -> IO () # peek :: Ptr Vulkan13Features -> IO Vulkan13Features # poke :: Ptr Vulkan13Features -> Vulkan13Features -> IO () # | |
Show Vulkan13Features Source # | |
Defined in Gpu.Vulkan.PhysicalDevice.Struct.Core showsPrec :: Int -> Vulkan13Features -> ShowS # show :: Vulkan13Features -> String # showList :: [Vulkan13Features] -> ShowS # |
pattern Vulkan13Features :: () -> PtrVoid -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Vulkan13Features Source #
data DescriptorIndexingFeatures Source #
Instances
Storable DescriptorIndexingFeatures Source # | |
Defined in Gpu.Vulkan.PhysicalDevice.Struct.Core sizeOf :: DescriptorIndexingFeatures -> Int # alignment :: DescriptorIndexingFeatures -> Int # peekElemOff :: Ptr DescriptorIndexingFeatures -> Int -> IO DescriptorIndexingFeatures # pokeElemOff :: Ptr DescriptorIndexingFeatures -> Int -> DescriptorIndexingFeatures -> IO () # peekByteOff :: Ptr b -> Int -> IO DescriptorIndexingFeatures # pokeByteOff :: Ptr b -> Int -> DescriptorIndexingFeatures -> IO () # peek :: Ptr DescriptorIndexingFeatures -> IO DescriptorIndexingFeatures # poke :: Ptr DescriptorIndexingFeatures -> DescriptorIndexingFeatures -> IO () # | |
Show DescriptorIndexingFeatures Source # | |
Defined in Gpu.Vulkan.PhysicalDevice.Struct.Core showsPrec :: Int -> DescriptorIndexingFeatures -> ShowS # show :: DescriptorIndexingFeatures -> String # showList :: [DescriptorIndexingFeatures] -> ShowS # |
pattern DescriptorIndexingFeatures :: () -> PtrVoid -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> DescriptorIndexingFeatures Source #
ShaderDrawParametersFeatures
data ShaderDrawParametersFeatures Source #
Instances
Storable ShaderDrawParametersFeatures Source # | |
Defined in Gpu.Vulkan.PhysicalDevice.Core sizeOf :: ShaderDrawParametersFeatures -> Int # alignment :: ShaderDrawParametersFeatures -> Int # peekElemOff :: Ptr ShaderDrawParametersFeatures -> Int -> IO ShaderDrawParametersFeatures # pokeElemOff :: Ptr ShaderDrawParametersFeatures -> Int -> ShaderDrawParametersFeatures -> IO () # peekByteOff :: Ptr b -> Int -> IO ShaderDrawParametersFeatures # pokeByteOff :: Ptr b -> Int -> ShaderDrawParametersFeatures -> IO () # peek :: Ptr ShaderDrawParametersFeatures -> IO ShaderDrawParametersFeatures # poke :: Ptr ShaderDrawParametersFeatures -> ShaderDrawParametersFeatures -> IO () # | |
Show ShaderDrawParametersFeatures Source # | |
Defined in Gpu.Vulkan.PhysicalDevice.Core showsPrec :: Int -> ShaderDrawParametersFeatures -> ShowS # show :: ShaderDrawParametersFeatures -> String # showList :: [ShaderDrawParametersFeatures] -> ShowS # |
pattern ShaderDrawParametersFeatures :: () -> PtrVoid -> Word32 -> ShaderDrawParametersFeatures Source #