Safe Haskell | None |
---|---|
Language | Haskell2010 |
Gpu.Vulkan.Middle
Synopsis
- data ApplicationInfo (mn :: Maybe Type) = ApplicationInfo {}
- data ApiVersion
- makeApiVersion :: Variant -> Major -> Minor -> Patch -> ApiVersion
- fromApiVersion :: ApiVersion -> (Variant, Major, Minor, Patch)
- type Variant = Word8
- type Major = Word8
- type Minor = Word16
- type Patch = Word16
- apiVersion_1_0 :: ApiVersion
- apiVersion_1_1 :: ApiVersion
- apiVersion_1_2 :: ApiVersion
- apiVersion_1_3 :: ApiVersion
- data SubmitInfo (mn :: Maybe Type) = SubmitInfo {
- submitInfoNext :: M mn
- submitInfoWaitSemaphoreDstStageMasks :: [(S, StageFlags)]
- submitInfoCommandBuffers :: [C]
- submitInfoSignalSemaphores :: [S]
- class SubmitInfoListToCore (ns :: [Maybe Type])
- data SubmitInfo2 (mn :: Maybe Type) (wsas :: [Maybe Type]) (cbas :: [Maybe Type]) (ssas :: [Maybe Type]) = SubmitInfo2 {}
- class SubmitInfo2ListToCore (si2as :: [(Maybe Type, [Maybe Type], [Maybe Type], [Maybe Type])])
- data LayerProperties = LayerProperties {}
- data ExtensionProperties = ExtensionProperties {}
- data FormatProperties = FormatProperties {}
- data 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 = StencilOpState {}
- data ClearValue (ct :: ClearType) where
- ClearValueColor :: forall (cct :: ClearColorType). Rgba Float -> ClearValue ('ClearTypeColor cct)
- ClearValueDepthStencil :: ClearDepthStencilValue -> ClearValue 'ClearTypeDepthStencil
- class Length cts => ClearValueListToCore (cts :: [ClearType])
- class ClearValueToCore (ct :: ClearType)
- data ClearType
- data ClearColorType
- class ClearColorValueToCore (cct :: ClearColorType)
- data ClearDepthStencilValue
- pattern ClearDepthStencilValue :: Float -> Word32 -> ClearDepthStencilValue
- clearDepthStencilValueDepth :: ClearDepthStencilValue -> Float
- clearDepthStencilValueStencil :: ClearDepthStencilValue -> Word32
- data 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
- 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
- newtype Size = Size Word64
- data DependencyInfo (mn :: Maybe Type) (mbs :: [Maybe Type]) (bmbs :: [Maybe Type]) (imbs :: [Maybe Type]) = DependencyInfo {}
- data BlitImageInfo2 (mn :: Maybe Type) (ras :: [Maybe Type]) = BlitImageInfo2 {}
- remainingMipLevels :: Word32
- remainingArrayLayers :: Word32
INFO
ApplicationInfo
data ApplicationInfo (mn :: Maybe Type) Source #
Constructors
ApplicationInfo | |
Instances
Show (M mn) => Show (ApplicationInfo mn) Source # | |
Defined in Gpu.Vulkan.Middle.Internal Methods showsPrec :: Int -> ApplicationInfo mn -> ShowS # show :: ApplicationInfo mn -> String # showList :: [ApplicationInfo mn] -> ShowS # |
data ApiVersion Source #
Instances
makeApiVersion :: Variant -> Major -> Minor -> Patch -> ApiVersion Source #
fromApiVersion :: ApiVersion -> (Variant, Major, Minor, Patch) Source #
SubmitInfo
data SubmitInfo (mn :: Maybe Type) Source #
Constructors
SubmitInfo | |
Fields
|
class SubmitInfoListToCore (ns :: [Maybe Type]) Source #
Minimal complete definition
submitInfoListToCore
Instances
SubmitInfoListToCore ('[] :: [Maybe Type]) Source # | |
Defined in Gpu.Vulkan.Middle.Internal Methods submitInfoListToCore :: PL SubmitInfo ('[] :: [Maybe Type]) -> ([SubmitInfo] -> IO a) -> IO () | |
(WithPoked (M n), SubmitInfoListToCore ns) => SubmitInfoListToCore (n ': ns) Source # | |
Defined in Gpu.Vulkan.Middle.Internal Methods submitInfoListToCore :: PL SubmitInfo (n ': ns) -> ([SubmitInfo] -> IO a) -> IO () |
data SubmitInfo2 (mn :: Maybe Type) (wsas :: [Maybe Type]) (cbas :: [Maybe Type]) (ssas :: [Maybe Type]) Source #
Constructors
SubmitInfo2 | |
Fields
|
class SubmitInfo2ListToCore (si2as :: [(Maybe Type, [Maybe Type], [Maybe Type], [Maybe Type])]) Source #
Minimal complete definition
submitInfo2ListToCore
Instances
SubmitInfo2ListToCore ('[] :: [(Maybe Type, [Maybe Type], [Maybe Type], [Maybe Type])]) Source # | |
Defined in Gpu.Vulkan.Middle.Internal Methods submitInfo2ListToCore :: PL (U4 SubmitInfo2) ('[] :: [(Maybe Type, [Maybe Type], [Maybe Type], [Maybe Type])]) -> ([SubmitInfo2] -> IO a) -> IO () | |
(WithPoked (M mn), ToListWithCCpsM' WithPoked M wsas, Length wsas, ToListWithCCpsM' WithPoked M cbas, Length cbas, ToListWithCCpsM' WithPoked M ssas, Length ssas, SubmitInfo2ListToCore si2as) => SubmitInfo2ListToCore ('(mn, wsas, cbas, ssas) ': si2as) Source # | |
Defined in Gpu.Vulkan.Middle.Internal Methods submitInfo2ListToCore :: PL (U4 SubmitInfo2) ('(mn, wsas, cbas, ssas) ': si2as) -> ([SubmitInfo2] -> IO a) -> IO () |
PROPERTIES
data LayerProperties Source #
Constructors
LayerProperties | |
Instances
Show LayerProperties Source # | |
Defined in Gpu.Vulkan.Middle.Internal Methods showsPrec :: Int -> LayerProperties -> ShowS # show :: LayerProperties -> String # showList :: [LayerProperties] -> ShowS # |
data ExtensionProperties Source #
Constructors
ExtensionProperties | |
Instances
Show ExtensionProperties Source # | |
Defined in Gpu.Vulkan.Middle.Internal Methods showsPrec :: Int -> ExtensionProperties -> ShowS # show :: ExtensionProperties -> String # showList :: [ExtensionProperties] -> ShowS # |
data FormatProperties Source #
Constructors
FormatProperties | |
Instances
Show FormatProperties Source # | |
Defined in Gpu.Vulkan.Middle.Internal Methods showsPrec :: Int -> FormatProperties -> ShowS # show :: FormatProperties -> String # showList :: [FormatProperties] -> ShowS # |
PIPELINE VALUES
ViewPort
Instances
Storable Viewport | |
Defined in Gpu.Vulkan.Core | |
Show Viewport | |
viewportWidth :: Viewport -> Float #
viewportHeight :: Viewport -> Float #
viewportMinDepth :: Viewport -> Float #
viewportMaxDepth :: Viewport -> Float #
StencilOpState
data StencilOpState Source #
Constructors
StencilOpState | |
Instances
Default StencilOpState Source # | |
Defined in Gpu.Vulkan.Middle.Internal Methods def :: StencilOpState # | |
Show StencilOpState Source # | |
Defined in Gpu.Vulkan.Middle.Internal Methods showsPrec :: Int -> StencilOpState -> ShowS # show :: StencilOpState -> String # showList :: [StencilOpState] -> ShowS # |
ClearValue
data ClearValue (ct :: ClearType) where Source #
Constructors
ClearValueColor :: forall (cct :: ClearColorType). Rgba Float -> ClearValue ('ClearTypeColor cct) | |
ClearValueDepthStencil :: ClearDepthStencilValue -> ClearValue 'ClearTypeDepthStencil |
Instances
Show (ClearValue ct) Source # | |
Defined in Gpu.Vulkan.Middle.Internal Methods showsPrec :: Int -> ClearValue ct -> ShowS # show :: ClearValue ct -> String # showList :: [ClearValue ct] -> ShowS # |
class Length cts => ClearValueListToCore (cts :: [ClearType]) Source #
Minimal complete definition
clearValueListToCore
Instances
ClearValueListToCore ('[] :: [ClearType]) Source # | |
Defined in Gpu.Vulkan.Middle.Internal Methods clearValueListToCore :: PL ClearValue ('[] :: [ClearType]) -> ([Ptr ClearValue] -> IO a) -> IO a | |
(ClearValueToCore ct, ClearValueListToCore cts) => ClearValueListToCore (ct ': cts) Source # | |
Defined in Gpu.Vulkan.Middle.Internal Methods clearValueListToCore :: PL ClearValue (ct ': cts) -> ([Ptr ClearValue] -> IO a) -> IO a |
class ClearValueToCore (ct :: ClearType) Source #
Minimal complete definition
clearValueToCore
Instances
ClearValueToCore 'ClearTypeDepthStencil Source # | |
Defined in Gpu.Vulkan.Middle.Internal Methods clearValueToCore :: ClearValue 'ClearTypeDepthStencil -> (Ptr ClearValue -> IO a) -> IO a | |
ClearColorValueToCore cct => ClearValueToCore ('ClearTypeColor cct) Source # | |
Defined in Gpu.Vulkan.Middle.Internal Methods clearValueToCore :: ClearValue ('ClearTypeColor cct) -> (Ptr ClearValue -> IO a) -> IO a |
ClearType
Constructors
ClearTypeColor ClearColorType | |
ClearTypeDepthStencil |
Instances
Show ClearType Source # | |
ClearValueListToCore ('[] :: [ClearType]) Source # | |
Defined in Gpu.Vulkan.Middle.Internal Methods clearValueListToCore :: PL ClearValue ('[] :: [ClearType]) -> ([Ptr ClearValue] -> IO a) -> IO a | |
(ClearValueToCore ct, ClearValueListToCore cts) => ClearValueListToCore (ct ': cts) Source # | |
Defined in Gpu.Vulkan.Middle.Internal Methods clearValueListToCore :: PL ClearValue (ct ': cts) -> ([Ptr ClearValue] -> IO a) -> IO a |
data ClearColorType Source #
Instances
Show ClearColorType Source # | |
Defined in Gpu.Vulkan.Middle.Internal Methods showsPrec :: Int -> ClearColorType -> ShowS # show :: ClearColorType -> String # showList :: [ClearColorType] -> ShowS # |
ClearColorValue
class ClearColorValueToCore (cct :: ClearColorType) Source #
Minimal complete definition
clearColorValueToCore
Instances
ClearColorValueToCore 'ClearColorTypeFloat32 Source # | |
Defined in Gpu.Vulkan.Middle.Internal Methods clearColorValueToCore :: ClearValue ('ClearTypeColor 'ClearColorTypeFloat32) -> (Ptr ClearColorValue -> IO a) -> IO a | |
ClearColorValueToCore 'ClearColorTypeInt32 Source # | |
Defined in Gpu.Vulkan.Middle.Internal Methods clearColorValueToCore :: ClearValue ('ClearTypeColor 'ClearColorTypeInt32) -> (Ptr ClearColorValue -> IO a) -> IO a | |
ClearColorValueToCore 'ClearColorTypeUint32 Source # | |
Defined in Gpu.Vulkan.Middle.Internal Methods clearColorValueToCore :: ClearValue ('ClearTypeColor 'ClearColorTypeUint32) -> (Ptr ClearColorValue -> IO a) -> IO a |
ClearDepthStencilValue
data ClearDepthStencilValue #
Instances
Storable ClearDepthStencilValue | |
Defined in Gpu.Vulkan.Core Methods 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 | |
Defined in Gpu.Vulkan.Core Methods showsPrec :: Int -> ClearDepthStencilValue -> ShowS # show :: ClearDepthStencilValue -> String # showList :: [ClearDepthStencilValue] -> ShowS # |
pattern ClearDepthStencilValue :: Float -> Word32 -> ClearDepthStencilValue #
RECT, OFFSET AND EXTENT
Rect
rect2dExtent :: Rect2d -> Extent2d #
rect2dOffset :: Rect2d -> Offset2d #
Offset
Instances
Storable Offset2d | |
Defined in Gpu.Vulkan.Core | |
Show Offset2d | |
Instances
Storable Offset3d | |
Defined in Gpu.Vulkan.Core | |
Show Offset3d | |
Extent
Instances
Storable Extent2d | |
Defined in Gpu.Vulkan.Core | |
Show Extent2d | |
extent2dWidth :: Extent2d -> Word32 #
extent2dHeight :: Extent2d -> Word32 #
Instances
Storable Extent3d | |
Defined in Gpu.Vulkan.Core | |
Show Extent3d | |
extent3dWidth :: Extent3d -> Word32 #
extent3dHeight :: Extent3d -> Word32 #
extent3dDepth :: Extent3d -> Word32 #
OTHERS
data DependencyInfo (mn :: Maybe Type) (mbs :: [Maybe Type]) (bmbs :: [Maybe Type]) (imbs :: [Maybe Type]) Source #
Constructors
DependencyInfo | |
Fields |
data BlitImageInfo2 (mn :: Maybe Type) (ras :: [Maybe Type]) Source #
Constructors
BlitImageInfo2 | |
Fields |