Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data ApplicationInfo
- type PtrApplicationInfo = Ptr ApplicationInfo
- pattern ApplicationInfo :: () -> PtrVoid -> CString -> ApiVersion -> CString -> ApiVersion -> ApiVersion -> ApplicationInfo
- applicationInfoSType :: ApplicationInfo -> ()
- applicationInfoPNext :: ApplicationInfo -> PtrVoid
- applicationInfoPApplicationName :: ApplicationInfo -> CString
- applicationInfoApplicationVersion :: ApplicationInfo -> ApiVersion
- applicationInfoPEngineName :: ApplicationInfo -> CString
- applicationInfoEngineVersion :: ApplicationInfo -> ApiVersion
- applicationInfoApiVersion :: ApplicationInfo -> ApiVersion
- type ApiVersion = Word32
- makeApiVersion :: Word8 -> Word8 -> Word16 -> Word16 -> ApiVersion
- apiVersion_1_0 :: ApiVersion
- apiVersion_1_1 :: ApiVersion
- apiVersion_1_2 :: ApiVersion
- apiVersion_1_3 :: ApiVersion
- data SubmitInfo
- pattern SubmitInfo :: () -> PtrVoid -> Word32 -> PtrS -> PtrPipelineStageFlags -> Word32 -> PtrC -> Int32 -> PtrS -> SubmitInfo
- submitInfoSType :: SubmitInfo -> ()
- submitInfoPNext :: SubmitInfo -> PtrVoid
- submitInfoWaitSemaphoreCount :: SubmitInfo -> Word32
- submitInfoPWaitSemaphores :: SubmitInfo -> PtrS
- submitInfoPWaitDstStageMask :: SubmitInfo -> PtrPipelineStageFlags
- type PtrPipelineStageFlags = Ptr Word32
- submitInfoCommandBufferCount :: SubmitInfo -> Word32
- submitInfoPCommandBuffers :: SubmitInfo -> PtrC
- submitInfoSignalSemaphoreCount :: SubmitInfo -> Int32
- submitInfoPSignalSemaphores :: SubmitInfo -> PtrS
- data SubmitInfo2
- pattern SubmitInfo2 :: () -> PtrVoid -> Word32 -> Word32 -> PtrSubmitInfo -> Word32 -> PtrSubmitInfo -> Word32 -> PtrSubmitInfo -> SubmitInfo2
- submitInfo2SType :: SubmitInfo2 -> ()
- submitInfo2PNext :: SubmitInfo2 -> PtrVoid
- submitInfo2Flags :: SubmitInfo2 -> Word32
- submitInfo2WaitSemaphoreInfoCount :: SubmitInfo2 -> Word32
- submitInfo2PWaitSemaphoreInfos :: SubmitInfo2 -> PtrSubmitInfo
- submitInfo2CommandBufferInfoCount :: SubmitInfo2 -> Word32
- submitInfo2PCommandBufferInfos :: SubmitInfo2 -> PtrSubmitInfo
- submitInfo2SignalSemaphoreInfoCount :: SubmitInfo2 -> Word32
- submitInfo2PSignalSemaphoreInfos :: SubmitInfo2 -> PtrSubmitInfo
- data ExtensionProperties
- pattern ExtensionProperties :: Text -> Word32 -> ExtensionProperties
- extensionPropertiesExtensionName :: ExtensionProperties -> Text
- extensionPropertiesSpecVersion :: ExtensionProperties -> Word32
- data LayerProperties
- pattern LayerProperties :: Text -> Word32 -> Word32 -> Text -> LayerProperties
- layerPropertiesLayerName :: LayerProperties -> Text
- layerPropertiesSpecVersion :: LayerProperties -> Word32
- layerPropertiesImplementationVersion :: LayerProperties -> Word32
- layerPropertiesDescription :: LayerProperties -> Text
- data FormatProperties
- pattern FormatProperties :: Word32 -> Word32 -> Word32 -> FormatProperties
- formatPropertiesLinearTilingFeatures :: FormatProperties -> Word32
- formatPropertiesOptimalTilingFeatures :: FormatProperties -> Word32
- formatPropertiesBufferFeatures :: FormatProperties -> Word32
- data Viewport
- type PtrViewport = Ptr Viewport
- pattern Viewport :: Float -> Float -> Float -> Float -> Float -> Float -> Viewport
- viewportX :: Viewport -> Float
- viewportY :: Viewport -> Float
- viewportWidth :: Viewport -> Float
- viewportHeight :: Viewport -> Float
- viewportMinDepth :: Viewport -> Float
- viewportMaxDepth :: Viewport -> Float
- data StencilOpState
- pattern StencilOpState :: Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> StencilOpState
- stencilOpStateFailOp :: StencilOpState -> Word32
- stencilOpStatePassOp :: StencilOpState -> Word32
- stencilOpStateDepthFailOp :: StencilOpState -> Word32
- stencilOpStateCompareOp :: StencilOpState -> Word32
- stencilOpStateCompareMask :: StencilOpState -> Word32
- stencilOpStateWriteMask :: StencilOpState -> Word32
- stencilOpStateReference :: StencilOpState -> Word32
- data ClearValue
- type PtrClearValue = Ptr ClearValue
- clearValueFromClearColorValue :: Ptr ClearColorValue -> Ptr ClearValue
- clearValueFromClearDepthStencilValue :: ClearDepthStencilValue -> (Ptr ClearValue -> IO a) -> IO a
- data ClearColorValue
- clearColorValueFromUints :: Ptr Word32 -> Ptr ClearColorValue
- clearColorValueFromInts :: Ptr Int32 -> Ptr ClearColorValue
- clearColorValueFromFloats :: Ptr Float -> Ptr ClearColorValue
- data ClearDepthStencilValue
- pattern ClearDepthStencilValue :: Float -> Word32 -> ClearDepthStencilValue
- clearDepthStencilValueDepth :: ClearDepthStencilValue -> Float
- clearDepthStencilValueStencil :: ClearDepthStencilValue -> Word32
- data StructCommon
- pattern StructCommon :: Word32 -> PtrVoid -> StructCommon
- structCommonSType :: StructCommon -> Word32
- structCommonPNext :: StructCommon -> PtrVoid
- data Rect2d
- type PtrRect2d = Ptr Rect2d
- pattern Rect2d :: Offset2d -> Extent2d -> Rect2d
- rect2dExtent :: Rect2d -> Extent2d
- rect2dOffset :: Rect2d -> Offset2d
- data Offset2d
- pattern Offset2d :: Int32 -> Int32 -> Offset2d
- offset2dX :: Offset2d -> Int32
- offset2dY :: Offset2d -> Int32
- data Offset3d
- type ListOffset3d = [Offset3d]
- pattern Offset3d :: Int32 -> Int32 -> Int32 -> Offset3d
- offset3dX :: Offset3d -> Int32
- offset3dY :: Offset3d -> Int32
- offset3dZ :: Offset3d -> Int32
- data Extent2d
- pattern Extent2d :: Word32 -> Word32 -> Extent2d
- extent2dWidth :: Extent2d -> Word32
- extent2dHeight :: Extent2d -> Word32
- data Extent3d
- pattern Extent3d :: Word32 -> Word32 -> Word32 -> Extent3d
- extent3dWidth :: Extent3d -> Word32
- extent3dHeight :: Extent3d -> Word32
- extent3dDepth :: Extent3d -> Word32
- data DependencyInfo
- pattern DependencyInfo :: () -> PtrVoid -> Word32 -> Word32 -> PtrBarrier2 -> Word32 -> PtrMemoryBarrier2 -> Word32 -> PtrMemoryBarrier2 -> DependencyInfo
- dependencyInfoSType :: DependencyInfo -> ()
- dependencyInfoPNext :: DependencyInfo -> PtrVoid
- dependencyInfoDependencyFlags :: DependencyInfo -> Word32
- dependencyInfoMemoryBarrierCount :: DependencyInfo -> Word32
- dependencyInfoPMemoryBarriers :: DependencyInfo -> PtrBarrier2
- dependencyInfoBufferMemoryBarrierCount :: DependencyInfo -> Word32
- dependencyInfoPBufferMemoryBarriers :: DependencyInfo -> PtrMemoryBarrier2
- dependencyInfoImageMemoryBarrierCount :: DependencyInfo -> Word32
- dependencyInfoPImageMemoryBarriers :: DependencyInfo -> PtrMemoryBarrier2
- data BlitImageInfo2
- pattern BlitImageInfo2 :: () -> PtrVoid -> I -> Word32 -> I -> Word32 -> Word32 -> PtrBlit2 -> Word32 -> BlitImageInfo2
- blitImageInfo2SType :: BlitImageInfo2 -> ()
- blitImageInfo2PNext :: BlitImageInfo2 -> PtrVoid
- blitImageInfo2SrcImage :: BlitImageInfo2 -> I
- blitImageInfo2SrcImageLayout :: BlitImageInfo2 -> Word32
- blitImageInfo2DstImage :: BlitImageInfo2 -> I
- blitImageInfo2DstImageLayout :: BlitImageInfo2 -> Word32
- blitImageInfo2RegionCount :: BlitImageInfo2 -> Word32
- blitImageInfo2PRegions :: BlitImageInfo2 -> PtrBlit2
- blitImageInfo2Filter :: BlitImageInfo2 -> Word32
INFO
ApplicationInfo
data ApplicationInfo Source #
Instances
Storable ApplicationInfo Source # | |
Defined in Gpu.Vulkan.Core sizeOf :: ApplicationInfo -> Int # alignment :: ApplicationInfo -> Int # peekElemOff :: Ptr ApplicationInfo -> Int -> IO ApplicationInfo # pokeElemOff :: Ptr ApplicationInfo -> Int -> ApplicationInfo -> IO () # peekByteOff :: Ptr b -> Int -> IO ApplicationInfo # pokeByteOff :: Ptr b -> Int -> ApplicationInfo -> IO () # peek :: Ptr ApplicationInfo -> IO ApplicationInfo # poke :: Ptr ApplicationInfo -> ApplicationInfo -> IO () # | |
Show ApplicationInfo Source # | |
Defined in Gpu.Vulkan.Core showsPrec :: Int -> ApplicationInfo -> ShowS # show :: ApplicationInfo -> String # showList :: [ApplicationInfo] -> ShowS # |
type PtrApplicationInfo = Ptr ApplicationInfo Source #
pattern ApplicationInfo :: () -> PtrVoid -> CString -> ApiVersion -> CString -> ApiVersion -> ApiVersion -> ApplicationInfo Source #
applicationInfoSType :: ApplicationInfo -> () Source #
ApiVersion
type ApiVersion = Word32 Source #
makeApiVersion :: Word8 -> Word8 -> Word16 -> Word16 -> ApiVersion Source #
SubmitInfo
data SubmitInfo Source #
Instances
Storable SubmitInfo Source # | |
Defined in Gpu.Vulkan.Core 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.Core showsPrec :: Int -> SubmitInfo -> ShowS # show :: SubmitInfo -> String # showList :: [SubmitInfo] -> ShowS # |
pattern SubmitInfo :: () -> PtrVoid -> Word32 -> PtrS -> PtrPipelineStageFlags -> Word32 -> PtrC -> Int32 -> PtrS -> SubmitInfo Source #
submitInfoSType :: SubmitInfo -> () Source #
submitInfoPNext :: SubmitInfo -> PtrVoid Source #
type PtrPipelineStageFlags = Ptr Word32 Source #
data SubmitInfo2 Source #
Instances
Storable SubmitInfo2 Source # | |
Defined in Gpu.Vulkan.Core sizeOf :: SubmitInfo2 -> Int # alignment :: SubmitInfo2 -> Int # peekElemOff :: Ptr SubmitInfo2 -> Int -> IO SubmitInfo2 # pokeElemOff :: Ptr SubmitInfo2 -> Int -> SubmitInfo2 -> IO () # peekByteOff :: Ptr b -> Int -> IO SubmitInfo2 # pokeByteOff :: Ptr b -> Int -> SubmitInfo2 -> IO () # peek :: Ptr SubmitInfo2 -> IO SubmitInfo2 # poke :: Ptr SubmitInfo2 -> SubmitInfo2 -> IO () # | |
Show SubmitInfo2 Source # | |
Defined in Gpu.Vulkan.Core showsPrec :: Int -> SubmitInfo2 -> ShowS # show :: SubmitInfo2 -> String # showList :: [SubmitInfo2] -> ShowS # |
pattern SubmitInfo2 :: () -> PtrVoid -> Word32 -> Word32 -> PtrSubmitInfo -> Word32 -> PtrSubmitInfo -> Word32 -> PtrSubmitInfo -> SubmitInfo2 Source #
submitInfo2SType :: SubmitInfo2 -> () Source #
submitInfo2Flags :: SubmitInfo2 -> Word32 Source #
PROPERTIES
ExtensionProperties
data ExtensionProperties Source #
Instances
Storable ExtensionProperties Source # | |
Defined in Gpu.Vulkan.Core sizeOf :: ExtensionProperties -> Int # alignment :: ExtensionProperties -> Int # peekElemOff :: Ptr ExtensionProperties -> Int -> IO ExtensionProperties # pokeElemOff :: Ptr ExtensionProperties -> Int -> ExtensionProperties -> IO () # peekByteOff :: Ptr b -> Int -> IO ExtensionProperties # pokeByteOff :: Ptr b -> Int -> ExtensionProperties -> IO () # peek :: Ptr ExtensionProperties -> IO ExtensionProperties # poke :: Ptr ExtensionProperties -> ExtensionProperties -> IO () # | |
Show ExtensionProperties Source # | |
Defined in Gpu.Vulkan.Core showsPrec :: Int -> ExtensionProperties -> ShowS # show :: ExtensionProperties -> String # showList :: [ExtensionProperties] -> ShowS # |
pattern ExtensionProperties :: Text -> Word32 -> ExtensionProperties Source #
LayerProperties
data LayerProperties Source #
Instances
Storable LayerProperties Source # | |
Defined in Gpu.Vulkan.Core sizeOf :: LayerProperties -> Int # alignment :: LayerProperties -> Int # peekElemOff :: Ptr LayerProperties -> Int -> IO LayerProperties # pokeElemOff :: Ptr LayerProperties -> Int -> LayerProperties -> IO () # peekByteOff :: Ptr b -> Int -> IO LayerProperties # pokeByteOff :: Ptr b -> Int -> LayerProperties -> IO () # peek :: Ptr LayerProperties -> IO LayerProperties # poke :: Ptr LayerProperties -> LayerProperties -> IO () # | |
Show LayerProperties Source # | |
Defined in Gpu.Vulkan.Core showsPrec :: Int -> LayerProperties -> ShowS # show :: LayerProperties -> String # showList :: [LayerProperties] -> ShowS # |
pattern LayerProperties :: Text -> Word32 -> Word32 -> Text -> LayerProperties Source #
FormatProperties
data FormatProperties Source #
Instances
Storable FormatProperties Source # | |
Defined in Gpu.Vulkan.Core sizeOf :: FormatProperties -> Int # alignment :: FormatProperties -> Int # peekElemOff :: Ptr FormatProperties -> Int -> IO FormatProperties # pokeElemOff :: Ptr FormatProperties -> Int -> FormatProperties -> IO () # peekByteOff :: Ptr b -> Int -> IO FormatProperties # pokeByteOff :: Ptr b -> Int -> FormatProperties -> IO () # peek :: Ptr FormatProperties -> IO FormatProperties # poke :: Ptr FormatProperties -> FormatProperties -> IO () # | |
Show FormatProperties Source # | |
Defined in Gpu.Vulkan.Core showsPrec :: Int -> FormatProperties -> ShowS # show :: FormatProperties -> String # showList :: [FormatProperties] -> ShowS # |
pattern FormatProperties :: Word32 -> Word32 -> Word32 -> FormatProperties Source #
PIPELINE VALUES
Viewport
Instances
Storable Viewport Source # | |
Show Viewport Source # | |
type PtrViewport = Ptr Viewport Source #
viewportWidth :: Viewport -> Float Source #
viewportHeight :: Viewport -> Float Source #
viewportMinDepth :: Viewport -> Float Source #
viewportMaxDepth :: Viewport -> Float Source #
StencilOpState
data StencilOpState Source #
Instances
Storable StencilOpState Source # | |
Defined in Gpu.Vulkan.Core sizeOf :: StencilOpState -> Int # alignment :: StencilOpState -> Int # peekElemOff :: Ptr StencilOpState -> Int -> IO StencilOpState # pokeElemOff :: Ptr StencilOpState -> Int -> StencilOpState -> IO () # peekByteOff :: Ptr b -> Int -> IO StencilOpState # pokeByteOff :: Ptr b -> Int -> StencilOpState -> IO () # peek :: Ptr StencilOpState -> IO StencilOpState # poke :: Ptr StencilOpState -> StencilOpState -> IO () # | |
Show StencilOpState Source # | |
Defined in Gpu.Vulkan.Core showsPrec :: Int -> StencilOpState -> ShowS # show :: StencilOpState -> String # showList :: [StencilOpState] -> ShowS # |
pattern StencilOpState :: Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> StencilOpState Source #
ClearValue
data ClearValue Source #
type PtrClearValue = Ptr ClearValue Source #
clearValueFromClearDepthStencilValue :: ClearDepthStencilValue -> (Ptr ClearValue -> IO a) -> IO a Source #
ClearColorValue
data ClearColorValue Source #
ClearDepthStencilValue
data ClearDepthStencilValue Source #
Instances
Storable ClearDepthStencilValue Source # | |
Defined in Gpu.Vulkan.Core sizeOf :: ClearDepthStencilValue -> Int # alignment :: ClearDepthStencilValue -> Int # peekElemOff :: Ptr ClearDepthStencilValue -> Int -> IO ClearDepthStencilValue # pokeElemOff :: Ptr ClearDepthStencilValue -> Int -> ClearDepthStencilValue -> IO () # peekByteOff :: Ptr b -> Int -> IO ClearDepthStencilValue # pokeByteOff :: Ptr b -> Int -> ClearDepthStencilValue -> IO () # peek :: Ptr ClearDepthStencilValue -> IO ClearDepthStencilValue # poke :: Ptr ClearDepthStencilValue -> ClearDepthStencilValue -> IO () # | |
Show ClearDepthStencilValue Source # | |
Defined in Gpu.Vulkan.Core showsPrec :: Int -> ClearDepthStencilValue -> ShowS # show :: ClearDepthStencilValue -> String # showList :: [ClearDepthStencilValue] -> ShowS # |
pattern ClearDepthStencilValue :: Float -> Word32 -> ClearDepthStencilValue Source #
STRUCT COMMON
data StructCommon Source #
Instances
Storable StructCommon Source # | |
Defined in Gpu.Vulkan.Core sizeOf :: StructCommon -> Int # alignment :: StructCommon -> Int # peekElemOff :: Ptr StructCommon -> Int -> IO StructCommon # pokeElemOff :: Ptr StructCommon -> Int -> StructCommon -> IO () # peekByteOff :: Ptr b -> Int -> IO StructCommon # pokeByteOff :: Ptr b -> Int -> StructCommon -> IO () # peek :: Ptr StructCommon -> IO StructCommon # poke :: Ptr StructCommon -> StructCommon -> IO () # | |
Show StructCommon Source # | |
Defined in Gpu.Vulkan.Core showsPrec :: Int -> StructCommon -> ShowS # show :: StructCommon -> String # showList :: [StructCommon] -> ShowS # |
pattern StructCommon :: Word32 -> PtrVoid -> StructCommon Source #
RECT, OFFSET AND EXTENT
Rect
Instances
rect2dExtent :: Rect2d -> Extent2d Source #
rect2dOffset :: Rect2d -> Offset2d Source #
Offset
Instances
Storable Offset2d Source # | |
Show Offset2d Source # | |
Instances
Storable Offset3d Source # | |
Show Offset3d Source # | |
type ListOffset3d = [Offset3d] Source #
Extent
Instances
Storable Extent2d Source # | |
Show Extent2d Source # | |
extent2dWidth :: Extent2d -> Word32 Source #
extent2dHeight :: Extent2d -> Word32 Source #
Instances
Storable Extent3d Source # | |
Show Extent3d Source # | |
extent3dWidth :: Extent3d -> Word32 Source #
extent3dHeight :: Extent3d -> Word32 Source #
extent3dDepth :: Extent3d -> Word32 Source #
DEPENDENCY INFO
data DependencyInfo Source #
Instances
Storable DependencyInfo Source # | |
Defined in Gpu.Vulkan.Core sizeOf :: DependencyInfo -> Int # alignment :: DependencyInfo -> Int # peekElemOff :: Ptr DependencyInfo -> Int -> IO DependencyInfo # pokeElemOff :: Ptr DependencyInfo -> Int -> DependencyInfo -> IO () # peekByteOff :: Ptr b -> Int -> IO DependencyInfo # pokeByteOff :: Ptr b -> Int -> DependencyInfo -> IO () # peek :: Ptr DependencyInfo -> IO DependencyInfo # poke :: Ptr DependencyInfo -> DependencyInfo -> IO () # | |
Show DependencyInfo Source # | |
Defined in Gpu.Vulkan.Core showsPrec :: Int -> DependencyInfo -> ShowS # show :: DependencyInfo -> String # showList :: [DependencyInfo] -> ShowS # |
pattern DependencyInfo :: () -> PtrVoid -> Word32 -> Word32 -> PtrBarrier2 -> Word32 -> PtrMemoryBarrier2 -> Word32 -> PtrMemoryBarrier2 -> DependencyInfo Source #
dependencyInfoSType :: DependencyInfo -> () Source #
BLIT IMAGE INFO 2
data BlitImageInfo2 Source #
Instances
Storable BlitImageInfo2 Source # | |
Defined in Gpu.Vulkan.Core sizeOf :: BlitImageInfo2 -> Int # alignment :: BlitImageInfo2 -> Int # peekElemOff :: Ptr BlitImageInfo2 -> Int -> IO BlitImageInfo2 # pokeElemOff :: Ptr BlitImageInfo2 -> Int -> BlitImageInfo2 -> IO () # peekByteOff :: Ptr b -> Int -> IO BlitImageInfo2 # pokeByteOff :: Ptr b -> Int -> BlitImageInfo2 -> IO () # peek :: Ptr BlitImageInfo2 -> IO BlitImageInfo2 # poke :: Ptr BlitImageInfo2 -> BlitImageInfo2 -> IO () # | |
Show BlitImageInfo2 Source # | |
Defined in Gpu.Vulkan.Core showsPrec :: Int -> BlitImageInfo2 -> ShowS # show :: BlitImageInfo2 -> String # showList :: [BlitImageInfo2] -> ShowS # |
pattern BlitImageInfo2 :: () -> PtrVoid -> I -> Word32 -> I -> Word32 -> Word32 -> PtrBlit2 -> Word32 -> BlitImageInfo2 Source #
blitImageInfo2SType :: BlitImageInfo2 -> () Source #