Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- create :: forall (mn :: Maybe Type) (fmt :: Format) (mac :: Maybe (Type, Type)) sd (nm :: Symbol) a. (WithPoked (M mn), FormatToValue fmt, ToMiddle mac) => D sd -> CreateInfo mn fmt -> M (U2 A) mac -> (forall s. I s nm fmt -> IO a) -> IO a
- unsafeRecreate :: forall (mn :: Maybe Type) (mac :: Maybe (Type, Type)) (fmt :: Format) sd sm si (nm :: Symbol). (WithPoked (M mn), ToMiddle mac, FormatToValue fmt) => D sd -> CreateInfo mn fmt -> M (U2 A) mac -> Binded sm si nm fmt -> IO ()
- unsafeRecreate' :: forall (mn :: Maybe Type) (mac :: Maybe (Type, Type)) (fmt :: Format) sd sm si (nm :: Symbol) a. (WithPoked (M mn), ToMiddle mac, FormatToValue fmt) => D sd -> CreateInfo mn fmt -> M (U2 A) mac -> Binded sm si nm fmt -> IO a -> IO ()
- newtype I s (nm :: Symbol) (fmt :: Format) = I I
- newtype Binded sm si (nm :: Symbol) (fmt :: Format) = Binded I
- data CreateInfo (mn :: Maybe Type) (fmt :: Format) = CreateInfo {
- createInfoNext :: M mn
- createInfoFlags :: CreateFlags
- createInfoImageType :: Type
- createInfoExtent :: Extent3d
- createInfoMipLevels :: Word32
- createInfoArrayLayers :: Word32
- createInfoSamples :: CountFlagBits
- createInfoTiling :: Tiling
- createInfoUsage :: UsageFlags
- createInfoSharingMode :: SharingMode
- createInfoQueueFamilyIndices :: [Index]
- createInfoInitialLayout :: Layout
- data Group sd (ma :: Maybe (Type, Type)) s k2 (nm :: k) (fmt :: k1)
- group :: forall {k1} {k2} (mac :: Maybe (Type, Type)) sd k3 (nm :: k1) (fmt :: k2) a. ToMiddle mac => D sd -> M (U2 A) mac -> (forall s. Group sd mac s k3 nm fmt -> IO a) -> IO a
- create' :: forall k (mn :: Maybe Type) (fmt :: Format) (mac :: Maybe (Type, Type)) sd sm (nm :: Symbol). (Ord k, WithPoked (M mn), FormatToValue fmt, ToMiddle mac) => Group sd mac sm k nm fmt -> k -> CreateInfo mn fmt -> IO (Either String (I sm nm fmt))
- unsafeDestroy :: forall {k1} {k2} k3 (mac :: Maybe (Type, Type)) sd sm (nm :: k1) (fmt :: k2). (Ord k3, ToMiddle mac) => Group sd mac sm k3 nm fmt -> k3 -> IO (Either String ())
- lookup :: forall k sd (ma :: Maybe (Type, Type)) smng (nm :: Symbol) (fmt :: Format). Ord k => Group sd ma smng k nm fmt -> k -> IO (Maybe (I smng nm fmt))
- getMemoryRequirements :: forall sd si (nm :: Symbol) (fmt :: Format). D sd -> I si nm fmt -> IO Requirements
- getMemoryRequirementsBinded :: forall sd sm si (nm :: Symbol) (fmt :: Format). D sd -> Binded sm si nm fmt -> IO Requirements
- data MemoryBarrier (mn :: Maybe Type) sm si (nm :: Symbol) (fmt :: Format) = MemoryBarrier {
- memoryBarrierNext :: M mn
- memoryBarrierSrcAccessMask :: AccessFlags
- memoryBarrierDstAccessMask :: AccessFlags
- memoryBarrierOldLayout :: Layout
- memoryBarrierNewLayout :: Layout
- memoryBarrierSrcQueueFamilyIndex :: Index
- memoryBarrierDstQueueFamilyIndex :: Index
- memoryBarrierImage :: Binded sm si nm fmt
- memoryBarrierSubresourceRange :: SubresourceRange
- data SubresourceRange = SubresourceRange {}
- class MemoryBarrierListToMiddle (mbargs :: [(Maybe Type, Type, Type, Symbol, Format)]) where
- memoryBarrierListToMiddle :: PL (U5 MemoryBarrier) mbargs -> PL MemoryBarrier (M0_5 mbargs)
- data Blit = Blit {}
- data SubresourceLayers = SubresourceLayers {}
CREATE
create :: forall (mn :: Maybe Type) (fmt :: Format) (mac :: Maybe (Type, Type)) sd (nm :: Symbol) a. (WithPoked (M mn), FormatToValue fmt, ToMiddle mac) => D sd -> CreateInfo mn fmt -> M (U2 A) mac -> (forall s. I s nm fmt -> IO a) -> IO a Source #
unsafeRecreate :: forall (mn :: Maybe Type) (mac :: Maybe (Type, Type)) (fmt :: Format) sd sm si (nm :: Symbol). (WithPoked (M mn), ToMiddle mac, FormatToValue fmt) => D sd -> CreateInfo mn fmt -> M (U2 A) mac -> Binded sm si nm fmt -> IO () Source #
unsafeRecreate' :: forall (mn :: Maybe Type) (mac :: Maybe (Type, Type)) (fmt :: Format) sd sm si (nm :: Symbol) a. (WithPoked (M mn), ToMiddle mac, FormatToValue fmt) => D sd -> CreateInfo mn fmt -> M (U2 A) mac -> Binded sm si nm fmt -> IO a -> IO () Source #
data CreateInfo (mn :: Maybe Type) (fmt :: Format) Source #
Instances
Show (M mn) => Show (CreateInfo mn fmt) Source # | |
Defined in Gpu.Vulkan.Image.Internal showsPrec :: Int -> CreateInfo mn fmt -> ShowS # show :: CreateInfo mn fmt -> String # showList :: [CreateInfo mn fmt] -> ShowS # |
Manage Destruction
group :: forall {k1} {k2} (mac :: Maybe (Type, Type)) sd k3 (nm :: k1) (fmt :: k2) a. ToMiddle mac => D sd -> M (U2 A) mac -> (forall s. Group sd mac s k3 nm fmt -> IO a) -> IO a Source #
create' :: forall k (mn :: Maybe Type) (fmt :: Format) (mac :: Maybe (Type, Type)) sd sm (nm :: Symbol). (Ord k, WithPoked (M mn), FormatToValue fmt, ToMiddle mac) => Group sd mac sm k nm fmt -> k -> CreateInfo mn fmt -> IO (Either String (I sm nm fmt)) Source #
unsafeDestroy :: forall {k1} {k2} k3 (mac :: Maybe (Type, Type)) sd sm (nm :: k1) (fmt :: k2). (Ord k3, ToMiddle mac) => Group sd mac sm k3 nm fmt -> k3 -> IO (Either String ()) Source #
lookup :: forall k sd (ma :: Maybe (Type, Type)) smng (nm :: Symbol) (fmt :: Format). Ord k => Group sd ma smng k nm fmt -> k -> IO (Maybe (I smng nm fmt)) Source #
GET MEMORY REQUIREMENTS
getMemoryRequirements :: forall sd si (nm :: Symbol) (fmt :: Format). D sd -> I si nm fmt -> IO Requirements Source #
getMemoryRequirementsBinded :: forall sd sm si (nm :: Symbol) (fmt :: Format). D sd -> Binded sm si nm fmt -> IO Requirements Source #
MEMORY BARRIER
data MemoryBarrier (mn :: Maybe Type) sm si (nm :: Symbol) (fmt :: Format) Source #
data SubresourceRange #
Instances
Show SubresourceRange | |
Defined in Gpu.Vulkan.Image.Middle.Internal showsPrec :: Int -> SubresourceRange -> ShowS # show :: SubresourceRange -> String # showList :: [SubresourceRange] -> ShowS # |
class MemoryBarrierListToMiddle (mbargs :: [(Maybe Type, Type, Type, Symbol, Format)]) where Source #
memoryBarrierListToMiddle :: PL (U5 MemoryBarrier) mbargs -> PL MemoryBarrier (M0_5 mbargs) Source #
Instances
MemoryBarrierListToMiddle ('[] :: [(Maybe Type, Type, Type, Symbol, Format)]) Source # | |
MemoryBarrierListToMiddle mbargs => MemoryBarrierListToMiddle ('(mn, si, sm, nm, fmt) ': mbargs) Source # | |
Defined in Gpu.Vulkan.Image.Internal memoryBarrierListToMiddle :: PL (U5 MemoryBarrier) ('(mn, si, sm, nm, fmt) ': mbargs) -> PL MemoryBarrier (M0_5 ('(mn, si, sm, nm, fmt) ': mbargs)) Source # |
BLIT
data SubresourceLayers #
Instances
Show SubresourceLayers | |
Defined in Gpu.Vulkan.Image.Middle.Internal showsPrec :: Int -> SubresourceLayers -> ShowS # show :: SubresourceLayers -> String # showList :: [SubresourceLayers] -> ShowS # |