Safe Haskell | None |
---|---|
Language | Haskell2010 |
Gpu.Vulkan.Khr.Swapchain
Synopsis
- extensionName :: ExtensionName
- create :: forall (mn :: Maybe Type) (fmt :: Format) (mac :: Maybe (Type, Type)) sd ssfc (mosas :: Maybe (Format, Type)) a. (WithPoked (M mn), FormatToValue fmt, ToMiddle mac) => D sd -> CreateInfo mn ssfc fmt mosas -> M (U2 A) mac -> (forall s. S fmt s -> IO a) -> IO a
- unsafeRecreate :: forall (mn :: Maybe Type) (fmt :: Format) (mac :: Maybe (Type, Type)) sd ssfc (mosas :: Maybe (Format, Type)) ssc. (WithPoked (M mn), FormatToValue fmt, ToMiddle mac) => D sd -> CreateInfo mn ssfc fmt mosas -> M (U2 A) mac -> S fmt ssc -> IO ()
- data S (fmt :: Format) ss
- data CreateInfo (mn :: Maybe Type) ssfc (fmt :: Format) (mosas :: Maybe (Format, Type)) = CreateInfo {
- createInfoNext :: M mn
- createInfoFlags :: CreateFlags
- createInfoSurface :: S ssfc
- createInfoMinImageCount :: Word32
- createInfoImageColorSpace :: ColorSpace
- createInfoImageExtent :: Extent2d
- createInfoImageArrayLayers :: Word32
- createInfoImageUsage :: UsageFlags
- createInfoImageSharingMode :: SharingMode
- createInfoQueueFamilyIndices :: [Index]
- createInfoPreTransform :: TransformFlagBits
- createInfoCompositeAlpha :: CompositeAlphaFlagBits
- createInfoPresentMode :: PresentMode
- createInfoClipped :: Bool
- createInfoOldSwapchain :: M (U2 S) mosas
- group :: forall (fmt :: Format) k sd (ma :: Maybe (Type, Type)) a. ToMiddle ma => D sd -> M (U2 A) ma -> (forall ssc. Group sd ma fmt ssc k -> IO a) -> IO a
- data Group sd (ma :: Maybe (Type, Type)) (fmt :: Format) ssc k
- create' :: forall (fmt :: Format) k (mn :: Maybe Type) (ma :: Maybe (Type, Type)) sd ss ssfc (mosas :: Maybe (Format, Type)). (FormatToValue fmt, Ord k, WithPoked (M mn), ToMiddle ma) => Group sd ma fmt ss k -> k -> CreateInfo mn ssfc fmt mosas -> IO (Either String (S fmt ss))
- unsafeDestroy :: forall k (ma :: Maybe (Type, Type)) sd (fmt :: Format) ssc. (Ord k, ToMiddle ma) => Group sd ma fmt ssc k -> k -> IO (Either String ())
- lookup :: forall k sd (ma :: Maybe (Type, Type)) (fmt :: Format) ssc. Ord k => Group sd ma fmt ssc k -> k -> IO (Maybe (S fmt ssc))
- getImages :: forall sd (fmt :: Format) ss (nm :: Symbol). D sd -> S fmt ss -> IO [Binded ss ss nm fmt]
- queuePresent :: forall (mn :: Maybe Type) (swss :: [Type]) (scfmt :: Format) (sscs :: [Type]). WithPoked (M mn) => Q -> PresentInfo mn swss scfmt sscs -> IO ()
- data PresentInfo (mn :: Maybe Type) (swss :: [Type]) (scfmt :: Format) (sscs :: [Type]) = PresentInfo {
- presentInfoNext :: M mn
- presentInfoWaitSemaphores :: PL S swss
- presentInfoSwapchainImageIndices :: PL (SwapchainImageIndex scfmt) sscs
- data SwapchainImageIndex (scfmt :: Format) ssc = SwapchainImageIndex (S scfmt ssc) Word32
- acquireNextImage :: forall sd (scfmt :: Format) ssc ss sf. D sd -> S scfmt ssc -> Maybe Sec -> Maybe (S ss) -> Maybe (F sf) -> IO Word32
- acquireNextImageResult :: forall sd (scfmt :: Format) ssc ss sf. [Result] -> D sd -> S scfmt ssc -> Maybe Sec -> Maybe (S ss) -> Maybe (F sf) -> IO Word32
EXTENSION NAME
CREATE
create :: forall (mn :: Maybe Type) (fmt :: Format) (mac :: Maybe (Type, Type)) sd ssfc (mosas :: Maybe (Format, Type)) a. (WithPoked (M mn), FormatToValue fmt, ToMiddle mac) => D sd -> CreateInfo mn ssfc fmt mosas -> M (U2 A) mac -> (forall s. S fmt s -> IO a) -> IO a Source #
unsafeRecreate :: forall (mn :: Maybe Type) (fmt :: Format) (mac :: Maybe (Type, Type)) sd ssfc (mosas :: Maybe (Format, Type)) ssc. (WithPoked (M mn), FormatToValue fmt, ToMiddle mac) => D sd -> CreateInfo mn ssfc fmt mosas -> M (U2 A) mac -> S fmt ssc -> IO () Source #
data CreateInfo (mn :: Maybe Type) ssfc (fmt :: Format) (mosas :: Maybe (Format, Type)) Source #
Constructors
Instances
(Show (M mn), Show (M (U2 S) mosas)) => Show (CreateInfo mn ss fmt mosas) Source # | |
Defined in Gpu.Vulkan.Khr.Swapchain Methods showsPrec :: Int -> CreateInfo mn ss fmt mosas -> ShowS # show :: CreateInfo mn ss fmt mosas -> String # showList :: [CreateInfo mn ss fmt mosas] -> ShowS # |
Group
group :: forall (fmt :: Format) k sd (ma :: Maybe (Type, Type)) a. ToMiddle ma => D sd -> M (U2 A) ma -> (forall ssc. Group sd ma fmt ssc k -> IO a) -> IO a Source #
create' :: forall (fmt :: Format) k (mn :: Maybe Type) (ma :: Maybe (Type, Type)) sd ss ssfc (mosas :: Maybe (Format, Type)). (FormatToValue fmt, Ord k, WithPoked (M mn), ToMiddle ma) => Group sd ma fmt ss k -> k -> CreateInfo mn ssfc fmt mosas -> IO (Either String (S fmt ss)) Source #
unsafeDestroy :: forall k (ma :: Maybe (Type, Type)) sd (fmt :: Format) ssc. (Ord k, ToMiddle ma) => Group sd ma fmt ssc k -> k -> IO (Either String ()) Source #
lookup :: forall k sd (ma :: Maybe (Type, Type)) (fmt :: Format) ssc. Ord k => Group sd ma fmt ssc k -> k -> IO (Maybe (S fmt ssc)) Source #
GET IMAGES
getImages :: forall sd (fmt :: Format) ss (nm :: Symbol). D sd -> S fmt ss -> IO [Binded ss ss nm fmt] Source #
QUEUE PRESENT
queuePresent :: forall (mn :: Maybe Type) (swss :: [Type]) (scfmt :: Format) (sscs :: [Type]). WithPoked (M mn) => Q -> PresentInfo mn swss scfmt sscs -> IO () Source #
data PresentInfo (mn :: Maybe Type) (swss :: [Type]) (scfmt :: Format) (sscs :: [Type]) Source #
Constructors
PresentInfo | |
Fields
|
data SwapchainImageIndex (scfmt :: Format) ssc Source #
Constructors
SwapchainImageIndex (S scfmt ssc) Word32 |
Instances
Show (SwapchainImageIndex scfmt ssc) Source # | |
Defined in Gpu.Vulkan.Khr.Swapchain Methods showsPrec :: Int -> SwapchainImageIndex scfmt ssc -> ShowS # show :: SwapchainImageIndex scfmt ssc -> String # showList :: [SwapchainImageIndex scfmt ssc] -> ShowS # |