gpu-vulkan-0.1.0.170: Vulkan library
Safe HaskellNone
LanguageHaskell2010

Gpu.Vulkan.Queue

Synopsis

SUBMIT AND WAIT IDLE

submit :: forall (sias :: [(Maybe Type, [Type], [Type], [Type])]) sf. SubmitInfoListToMiddle sias => Q -> PL (U4 SubmitInfo) sias -> Maybe (F sf) -> IO () Source #

submit2 :: forall (sias :: [(Maybe Type, [(Maybe Type, Type)], [(Maybe Type, Type)], [(Maybe Type, Type)])]) sf. SubmitInfo2ListToMiddle sias => Q -> PL (U4 SubmitInfo2) sias -> Maybe (F sf) -> IO () Source #

waitIdle :: Q -> IO () #

data Q #

Instances

Instances details
Show Q 
Instance details

Defined in Gpu.Vulkan.Queue.Middle.Internal

Methods

showsPrec :: Int -> Q -> ShowS #

show :: Q -> String #

showList :: [Q] -> ShowS #

TYPE SYNONYM

SPARSE RESOURCES

bindSparse :: forall (ias :: [(Maybe Type, [Type], [(Type, Symbol, [O], [(Type, [(Type, ImageBufferArg)], Nat)])], [(Type, Symbol, Format, [(Type, [(Type, ImageBufferArg)], Nat)])], [(Type, Symbol, Format, [(Type, [(Type, ImageBufferArg)], Nat)])], [Type])]) sd sf. (BindSparseInfosToMiddle ias, ToListWithCCpsM' WithPoked M (M0_6 ias)) => D sd -> Q -> PL (U6 BindSparseInfo) ias -> Maybe (F sf) -> IO () Source #

class BindSparseInfosToMiddle (bsias :: [(Maybe Type, [Type], [(Type, Symbol, [O], [(Type, [(Type, ImageBufferArg)], Nat)])], [(Type, Symbol, Format, [(Type, [(Type, ImageBufferArg)], Nat)])], [(Type, Symbol, Format, [(Type, [(Type, ImageBufferArg)], Nat)])], [Type])]) Source #

Minimal complete definition

bindSparseInfosToMiddle

Instances

Instances details
BindSparseInfosToMiddle ('[] :: [(Maybe Type, [Type], [(Type, Symbol, [O], [(Type, [(Type, ImageBufferArg)], Nat)])], [(Type, Symbol, Format, [(Type, [(Type, ImageBufferArg)], Nat)])], [(Type, Symbol, Format, [(Type, [(Type, ImageBufferArg)], Nat)])], [Type])]) Source # 
Instance details

Defined in Gpu.Vulkan.Queue

Methods

bindSparseInfosToMiddle :: D sd -> PL (U6 BindSparseInfo) ('[] :: [(Maybe Type, [Type], [(Type, Symbol, [O], [(Type, [(Type, ImageBufferArg)], Nat)])], [(Type, Symbol, Format, [(Type, [(Type, ImageBufferArg)], Nat)])], [(Type, Symbol, Format, [(Type, [(Type, ImageBufferArg)], Nat)])], [Type])]) -> IO (PL BindSparseInfo (M0_6 ('[] :: [(Maybe Type, [Type], [(Type, Symbol, [O], [(Type, [(Type, ImageBufferArg)], Nat)])], [(Type, Symbol, Format, [(Type, [(Type, ImageBufferArg)], Nat)])], [(Type, Symbol, Format, [(Type, [(Type, ImageBufferArg)], Nat)])], [Type])])))

(MemoryBindInfosToMiddle bbs, OpaqueMemoryBindInfosToMiddle iobs, MemoryBindInfosToMiddle ibs, BindSparseInfosToMiddle bsias) => BindSparseInfosToMiddle ('(mn, swss, bbs, iobs, ibs, ssss) ': bsias) Source # 
Instance details

Defined in Gpu.Vulkan.Queue

Methods

bindSparseInfosToMiddle :: D sd -> PL (U6 BindSparseInfo) ('(mn, swss, bbs, iobs, ibs, ssss) ': bsias) -> IO (PL BindSparseInfo (M0_6 ('(mn, swss, bbs, iobs, ibs, ssss) ': bsias)))

ENUM

newtype FlagBits #

Constructors

FlagBits Word32 

Instances

Instances details
Bits FlagBits 
Instance details

Defined in Gpu.Vulkan.Queue.Enum

FiniteBits FlagBits 
Instance details

Defined in Gpu.Vulkan.Queue.Enum

Storable FlagBits 
Instance details

Defined in Gpu.Vulkan.Queue.Enum

Show FlagBits 
Instance details

Defined in Gpu.Vulkan.Queue.Enum

Eq FlagBits 
Instance details

Defined in Gpu.Vulkan.Queue.Enum

pattern ComputeBit :: FlagBits #

pattern FlagsZero :: FlagBits #