Safe Haskell | None |
---|---|
Language | Haskell2010 |
Gpu.Vulkan.Queue
Synopsis
- submit :: forall (sias :: [(Maybe Type, [Type], [Type], [Type])]) sf. SubmitInfoListToMiddle sias => Q -> PL (U4 SubmitInfo) sias -> Maybe (F sf) -> IO ()
- 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 ()
- waitIdle :: Q -> IO ()
- data Q
- type Index = Word32
- 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 ()
- data BindSparseInfo (mn :: Maybe Type) (swss :: [Type]) (bbs :: [(Type, Symbol, [O], [(Type, [(Type, ImageBufferArg)], Nat)])]) (iobs :: [(Type, Symbol, Format, [(Type, [(Type, ImageBufferArg)], Nat)])]) (ibs :: [(Type, Symbol, Format, [(Type, [(Type, ImageBufferArg)], Nat)])]) (ssss :: [Type]) = BindSparseInfo {
- bindSparseInfoNext :: M mn
- bindSparseInfoWaitSemaphores :: PL S swss
- bindSparseInfoBufferBinds :: PL (U4 MemoryBindInfo) bbs
- bindSparseInfoImageOpaqueBinds :: PL (U4 OpaqueMemoryBindInfo) iobs
- bindSparseInfoImageBinds :: PL (U4 MemoryBindInfo) ibs
- bindSparseInfoSignalSemaphores :: PL S ssss
- 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])])
- type Flags = FlagBits
- newtype FlagBits = FlagBits Word32
- pattern FlagBitsMaxEnum :: FlagBits
- unFlagBits :: FlagBits -> Word32
- pattern OpticalFlowBitNv :: FlagBits
- pattern VideoEncodeBitKhr :: FlagBits
- pattern VideoDecodeBitKhr :: FlagBits
- pattern ProtectedBit :: FlagBits
- pattern SparseBindingBit :: FlagBits
- pattern TransferBit :: FlagBits
- pattern ComputeBit :: FlagBits
- pattern GraphicsBit :: FlagBits
- pattern FlagsZero :: FlagBits
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 #
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 #
data BindSparseInfo (mn :: Maybe Type) (swss :: [Type]) (bbs :: [(Type, Symbol, [O], [(Type, [(Type, ImageBufferArg)], Nat)])]) (iobs :: [(Type, Symbol, Format, [(Type, [(Type, ImageBufferArg)], Nat)])]) (ibs :: [(Type, Symbol, Format, [(Type, [(Type, ImageBufferArg)], Nat)])]) (ssss :: [Type]) Source #
Constructors
BindSparseInfo | |
Fields
|
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
ENUM
Instances
Bits FlagBits | |
Defined in Gpu.Vulkan.Queue.Enum Methods (.&.) :: FlagBits -> FlagBits -> FlagBits # (.|.) :: FlagBits -> FlagBits -> FlagBits # xor :: FlagBits -> FlagBits -> FlagBits # complement :: FlagBits -> FlagBits # shift :: FlagBits -> Int -> FlagBits # rotate :: FlagBits -> Int -> FlagBits # setBit :: FlagBits -> Int -> FlagBits # clearBit :: FlagBits -> Int -> FlagBits # complementBit :: FlagBits -> Int -> FlagBits # testBit :: FlagBits -> Int -> Bool # bitSizeMaybe :: FlagBits -> Maybe Int # isSigned :: FlagBits -> Bool # shiftL :: FlagBits -> Int -> FlagBits # unsafeShiftL :: FlagBits -> Int -> FlagBits # shiftR :: FlagBits -> Int -> FlagBits # unsafeShiftR :: FlagBits -> Int -> FlagBits # rotateL :: FlagBits -> Int -> FlagBits # | |
FiniteBits FlagBits | |
Defined in Gpu.Vulkan.Queue.Enum Methods finiteBitSize :: FlagBits -> Int # countLeadingZeros :: FlagBits -> Int # countTrailingZeros :: FlagBits -> Int # | |
Storable FlagBits | |
Defined in Gpu.Vulkan.Queue.Enum | |
Show FlagBits | |
Eq FlagBits | |
pattern FlagBitsMaxEnum :: FlagBits #
unFlagBits :: FlagBits -> Word32 #
pattern OpticalFlowBitNv :: FlagBits #
pattern VideoEncodeBitKhr :: FlagBits #
pattern VideoDecodeBitKhr :: FlagBits #
pattern ProtectedBit :: FlagBits #
pattern SparseBindingBit :: FlagBits #
pattern TransferBit :: FlagBits #
pattern ComputeBit :: FlagBits #
pattern GraphicsBit :: FlagBits #