gpu-vulkan-0.1.0.166: Vulkan library
Safe HaskellNone
LanguageHaskell2010

Gpu.Vulkan.Cmd

Synopsis

BEGIN RENDER PASS

beginRenderPass :: forall (mn :: Maybe Type) (cts :: [ClearType]) scb sr sf a. (WithPoked (M mn), ClearValueListToCore cts) => C scb -> BeginInfo mn sr sf cts -> Contents -> IO a -> IO a Source #

DRAW AND DISPATCH

Draw

bindPipelineGraphics :: forall scb sg (vibs :: [(Type, Rate)]) (vias :: [(Nat, Type)]) (slbtss :: (Type, [(Type, [BindingType])], [Type])) a. C scb -> BindPoint -> G sg vibs vias slbtss -> (forall sgb. GBinded sgb vibs slbtss -> IO a) -> IO a Source #

bindVertexBuffers :: forall sg (vibs :: [(Type, Rate)]) (slbtss :: (Type, [(Type, [BindingType])], [Type])) (smsbnmts :: [(Type, Type, Symbol, Type, Symbol)]). InfixIndex (M3_5 smsbnmts) (M0_2 vibs) => GBinded sg vibs slbtss -> PL (U5 (IndexedForList :: Type -> Type -> Symbol -> Type -> Symbol -> Type)) smsbnmts -> IO () Source #

bindIndexBuffer :: forall {k} sg (vibs :: [(Type, Rate)]) (slbtss :: (Type, [(Type, [BindingType])], [Type])) sm sb (nm :: Symbol) (i :: k) (onm :: Symbol). IsIndex i => GBinded sg vibs slbtss -> IndexedForList sm sb nm i onm -> IO () Source #

class IsIndex (a :: k) Source #

Minimal complete definition

indexType

Instances

Instances details
IsIndex Word16 Source # 
Instance details

Defined in Gpu.Vulkan.Cmd

IsIndex Word32 Source # 
Instance details

Defined in Gpu.Vulkan.Cmd

draw :: forall sc (vibs :: [(Type, Rate)]) (slbtss :: (Type, [(Type, [BindingType])], [Type])). GBinded sc vibs slbtss -> VertexCount -> InstanceCount -> FirstVertex -> FirstInstance -> IO () Source #

drawIndexed :: forall sc (vibs :: [(Type, Rate)]) (slbtss :: (Type, [(Type, [BindingType])], [Type])). GBinded sc vibs slbtss -> IndexCount -> InstanceCount -> FirstIndex -> VertexOffset -> FirstInstance -> IO () Source #

Dispatch

bindPipelineCompute :: forall {k} scmdb (scp :: k) (slbtss :: (Type, [(Type, [BindingType])], [Type])) a. C scmdb -> BindPoint -> C scp slbtss -> (forall scbnd. CBinded scbnd slbtss -> IO a) -> IO a Source #

dispatch :: forall sc (slbtss :: (Type, [(Type, [BindingType])], [Type])). CBinded sc slbtss -> GroupCountX -> GroupCountY -> GroupCountZ -> IO () Source #

PUSH CONSTANTS AND BIND DESCRIPTOR SETS

pushConstantsGraphics :: forall (sss :: [ShaderStageFlagBits]) sc (vibs :: [(Type, Rate)]) sl (sbtss :: [(Type, [BindingType])]) (pcs :: [Type]) (ts :: [Type]). (ShaderStageFlagBitsListToValue sss, PokableList ts, InfixOffsetSize ts pcs) => GBinded sc vibs '(sl, sbtss, pcs) -> P sl sbtss pcs -> L ts -> IO () Source #

pushConstantsCompute :: forall (sss :: [ShaderStageFlagBits]) sc sl (sbtss :: [(Type, [BindingType])]) (pcs :: [Type]) (ts :: [Type]). (ShaderStageFlagBitsListToValue sss, PokableList ts, InfixOffsetSize ts pcs) => CBinded sc '(sl, sbtss, pcs) -> P sl sbtss pcs -> L ts -> IO () Source #

bindDescriptorSetsGraphics :: forall sgbnd (vibs :: [(Type, Rate)]) sl (dsls :: [(Type, [BindingType])]) (pcs :: [Type]) (dss :: [(Type, (Type, [BindingType]))]) (dsls' :: [(Type, [BindingType])]) (dyns :: [[[O]]]). (M1_2 dss ~ dsls', LayoutArgListOnlyDynamics dsls' ~ dyns, InfixIndex dsls' dsls, GetDynamicLength dss, ZipListWithC3 SizeAlignment dyns) => GBinded sgbnd vibs '(sl, dsls, pcs) -> BindPoint -> P sl dsls pcs -> PL (U2 D) dss -> PL3 DynamicIndex dyns -> IO () Source #

bindDescriptorSetsCompute :: forall scbnd sl (dsls :: [(Type, [BindingType])]) (pcs :: [Type]) (dss :: [(Type, (Type, [BindingType]))]) (dsls' :: [(Type, [BindingType])]) (dyns :: [[[O]]]). (M1_2 dss ~ dsls', LayoutArgListOnlyDynamics dsls' ~ dyns, InfixIndex dsls' dsls, GetDynamicLength dss, ZipListWithC3 SizeAlignment dyns) => CBinded scbnd '(sl, dsls, pcs) -> P sl dsls pcs -> PL (U2 D) dss -> PL3 DynamicIndex dyns -> IO () Source #

newtype DynamicIndex (obj :: O) Source #

Constructors

DynamicIndex Word32 

Instances

Instances details
Show (DynamicIndex obj) Source # 
Instance details

Defined in Gpu.Vulkan.Cmd

class GetDynamicLength (sspslbtss :: [(Type, (Type, [BindingType]))]) Source #

Minimal complete definition

getDynamicLength

Instances

Instances details
GetDynamicLength ('[] :: [(Type, (Type, [BindingType]))]) Source # 
Instance details

Defined in Gpu.Vulkan.Cmd

Methods

getDynamicLength :: PL (U2 D) ('[] :: [(Type, (Type, [BindingType]))]) -> IO (PL3 Length (LayoutArgListOnlyDynamics (M1_2 ('[] :: [(Type, (Type, [BindingType]))]))))

GetDynamicLength spslbtss => GetDynamicLength (slbts ': spslbtss) Source # 
Instance details

Defined in Gpu.Vulkan.Cmd

Methods

getDynamicLength :: PL (U2 D) (slbts ': spslbtss) -> IO (PL3 Length (LayoutArgListOnlyDynamics (M1_2 (slbts ': spslbtss))))

COPY BUFFER AND IMAGES

copyBuffer :: forall (cpobjss :: [([O], Nat, Nat)]) scb sms sbs (nms :: Symbol) (objss :: [O]) smd sbd (nmd :: Symbol) (objsd :: [O]). MakeCopies cpobjss objss objsd => C scb -> Binded sms sbs nms objss -> Binded smd sbd nmd objsd -> IO () Source #

copyBufferToImage :: forall (algn :: Nat) img (inms :: [Symbol]) scb smb sbb (bnm :: Symbol) (objs :: [O]) smi si (inm :: Symbol). ImageCopyListToMiddle algn objs img inms => C scb -> Binded smb sbb bnm objs -> Binded smi si inm (ImageFormat img) -> Layout -> PL (ImageCopy img :: Symbol -> Type) inms -> IO () Source #

copyImageToBuffer :: forall (algn :: Nat) img (inms :: [Symbol]) scb smi si (inm :: Symbol) smb sbb (bnm :: Symbol) (objs :: [O]). ImageCopyListToMiddle algn objs img inms => C scb -> Binded smi si inm (ImageFormat img) -> Layout -> Binded smb sbb bnm objs -> PL (ImageCopy img :: Symbol -> Type) inms -> IO () Source #

blitImage :: forall scb sms sis (nms :: Symbol) (fmts :: Format) smd sid (nmd :: Symbol) (fmtd :: Format). C scb -> Binded sms sis nms fmts -> Layout -> Binded smd sid nmd fmtd -> Layout -> [Blit] -> Filter -> IO () Source #

blitImage2 :: forall (mn :: Maybe Type) (ras :: [Maybe Type]) scb sms sis (nms :: Symbol) (fmts :: Format) smd sid (nmd :: Symbol) (fmtd :: Format). (WithPoked (M mn), Length ras, ToListWithCCpsM' WithPoked M ras) => C scb -> BlitImageInfo2 mn sms sis nms fmts smd sid nmd fmtd ras -> IO () Source #

CLEAR COLOR IMAGE

clearColorImage :: forall (cct :: ClearColorType) sc sm si (nm :: Symbol) (fmt :: Format). ClearColorValueToCore cct => C sc -> Binded sm si nm fmt -> Layout -> ClearValue ('ClearTypeColor cct) -> [SubresourceRange] -> IO () Source #

MEMORY DEPENDENCY

pipelineBarrier :: forall (mbargs :: [Maybe Type]) (bmbargss :: [(Maybe Type, Type, Type, Symbol, O)]) (imbargss :: [(Maybe Type, Type, Type, Symbol, Format)]) scb. (ToListWithCCpsM' WithPoked M mbargs, ToListWithCCpsM' WithPoked M (M0_5 bmbargss), ToListWithCCpsM' WithPoked M (M0_5 imbargss), MemoryBarrierListToMiddle bmbargss, MemoryBarrierListToMiddle imbargss) => C scb -> StageFlags -> StageFlags -> DependencyFlags -> PL Barrier mbargs -> PL (U5 MemoryBarrier) bmbargss -> PL (U5 MemoryBarrier) imbargss -> IO () Source #

pipelineBarrier2 :: forall (mn :: Maybe Type) (mbas :: [Maybe Type]) (bmbas :: [(Maybe Type, Type, Type, Symbol, O)]) (imbas :: [(Maybe Type, Type, Type, Symbol, Format)]) scb. (WithPoked (M mn), ToListWithCCpsM' WithPoked M mbas, Length mbas, ToListWithCCpsM' WithPoked M (M0_5 bmbas), Length (M0_5 bmbas), ToListWithCCpsM' WithPoked M (M0_5 imbas), Length (M0_5 imbas), MemoryBarrier2ListToMiddle bmbas, MemoryBarrier2ListToMiddle imbas) => C scb -> DependencyInfo mn mbas bmbas imbas -> IO () Source #

QUERY

resetQueryPool :: forall sc sq (tp :: Bool -> Type). C sc -> Q sq tp -> First -> Count -> IO () Source #

beginQuery :: forall sc sq (tp :: Bool -> Type) a. C sc -> Q sq tp -> Q -> ControlFlags -> IO a -> IO () Source #

writeTimestamp :: C sc -> StageFlagBits -> Q sq Timestamp -> Q -> IO () Source #

OTHERS

type family LayoutArgListOnlyDynamics (las :: [(k0, [BindingType])]) :: [[[O]]] where ... Source #

Equations

LayoutArgListOnlyDynamics ('[] :: [(k0, [BindingType])]) = '[] :: [[[O]]] 
LayoutArgListOnlyDynamics (la ': las :: [(k0, [BindingType])]) = BindingTypeListBufferOnlyDynamics (I1_2 la) ': LayoutArgListOnlyDynamics las