{-# LANGUAGE ImportQualifiedPost #-}
{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE ScopedTypeVariables, RankNTypes, TypeApplications #-}
{-# LANGUAGE GADTs, TypeFamilies #-}
{-# LANGUAGE DataKinds, PolyKinds #-}
{-# LANGUAGE KindSignatures, TypeOperators #-}
{-# LANGUAGE MultiParamTypeClasses, AllowAmbiguousTypes #-}
{-# LANGUAGE FlexibleContexts, FlexibleInstances, UndecidableInstances #-}
{-# LANGUAGE PatternSynonyms, ViewPatterns #-}
{-# LANGUAGe StandaloneDeriving #-}
{-# OPTIONS_GHC -Wall -fno-warn-tabs #-}
module Gpu.Vulkan.Cmd (
beginRenderPass,
bindPipelineGraphics,
bindVertexBuffers, bindIndexBuffer, IsIndex,
draw, drawIndexed,
VertexCount, IndexCount, InstanceCount,
FirstVertex, FirstIndex, FirstInstance,
VertexOffset,
bindPipelineCompute, dispatch, GroupCountX, GroupCountY, GroupCountZ,
pushConstantsGraphics, pushConstantsCompute,
bindDescriptorSetsGraphics, bindDescriptorSetsCompute,
DynamicIndex(..), GetDynamicLength,
copyBuffer, copyBufferToImage, copyImageToBuffer, blitImage, blitImage2,
clearColorImage,
pipelineBarrier, pipelineBarrier2,
resetQueryPool,
beginQuery,
writeTimestamp,
LayoutArgListOnlyDynamics
) where
import GHC.TypeNats
import Foreign.Storable.PeekPoke
import Foreign.Storable.HeteroList
import Control.Exception
import Data.TypeLevel.Maybe qualified as TMaybe
import Data.TypeLevel.List
import Data.TypeLevel.Tuple.Uncurry
import Data.TypeLevel.Tuple.Index qualified as TIndex
import Data.TypeLevel.Tuple.MapIndex qualified as TMapIndex
import qualified Data.HeteroParList as HPList
import qualified Data.HeteroParList as HeteroParList
import Data.HeteroParList (pattern (:**))
import Data.Word
import Data.Int
import Gpu.Vulkan
import Gpu.Vulkan.Internal
import Gpu.Vulkan.TypeEnum qualified as T
import qualified Gpu.Vulkan.CommandBuffer as CommandBuffer
import qualified Gpu.Vulkan.CommandBuffer.Type as CommandBuffer.T
import qualified Gpu.Vulkan.Pipeline.Graphics.Type as Pipeline
import qualified Gpu.Vulkan.Pipeline.Compute as Pipeline.Compute
import qualified Gpu.Vulkan.Pipeline.Enum as Pipeline
import qualified Gpu.Vulkan.PipelineLayout.Type as PipelineLayout
import qualified Gpu.Vulkan.DescriptorSet as DescriptorSet
import qualified Gpu.Vulkan.DescriptorSet.Type as DescriptorSet
import qualified Gpu.Vulkan.DescriptorSetLayout.Type as Layout
import qualified Gpu.Vulkan.Buffer.Type as Bffr
import qualified Gpu.Vulkan.Buffer as Bffr
import qualified Gpu.Vulkan.Buffer.Internal as Bffr.I
import qualified Gpu.Vulkan.Image as Image
import qualified Gpu.Vulkan.Image.Internal as Image.I
import qualified Gpu.Vulkan.Image.Type as Image
import qualified Gpu.Vulkan.Image.Middle as Image.M
import qualified Gpu.Vulkan.RenderPass.Internal as RenderPass
import qualified Gpu.Vulkan.Subpass.Enum as Subpass
import qualified Gpu.Vulkan.Cmd.Middle as M
import qualified Gpu.Vulkan.Middle as M
import qualified Gpu.Vulkan.Memory as Memory
import Data.IORef
import Gpu.Vulkan.Query.Enum qualified as Query
import Gpu.Vulkan.QueryPool qualified as QueryPool
import Gpu.Vulkan.QueryPool.Type qualified as QueryPool
import Gpu.Vulkan.Query qualified as Query
import Gpu.Vulkan.Object.Base qualified as KObj
beginRenderPass :: (WithPoked (TMaybe.M mn), ClearValueListToCore cts) =>
CommandBuffer.C scb -> RenderPass.BeginInfo mn sr sf cts ->
Subpass.Contents -> IO a -> IO a
beginRenderPass :: forall (mn :: Maybe (*)) (cts :: [ClearType]) scb sr sf a.
(WithPoked (M mn), ClearValueListToCore cts) =>
C scb -> BeginInfo mn sr sf cts -> Contents -> IO a -> IO a
beginRenderPass (CommandBuffer.T.C C
cb) BeginInfo mn sr sf cts
bi Contents
cnt IO a
f = IO () -> IO () -> IO a -> IO a
forall a b c. IO a -> IO b -> IO c -> IO c
bracket_
(C -> BeginInfo mn cts -> Contents -> IO ()
forall (mn :: Maybe (*)) (cts :: [ClearType]).
(WithPoked (M mn), ClearValueListToCore cts) =>
C -> BeginInfo mn cts -> Contents -> IO ()
M.beginRenderPass C
cb (BeginInfo mn sr sf cts -> BeginInfo mn cts
forall (n :: Maybe (*)) sr sf (cts :: [ClearType]).
BeginInfo n sr sf cts -> BeginInfo n cts
RenderPass.beginInfoToMiddle BeginInfo mn sr sf cts
bi) Contents
cnt)
(C -> IO ()
M.endRenderPass C
cb) IO a
f
bindPipelineGraphics :: CommandBuffer.C scb ->
Pipeline.BindPoint -> Pipeline.G sg vibs vias slbtss ->
(forall sgb . CommandBuffer.GBinded sgb vibs slbtss -> IO a) -> IO a
bindPipelineGraphics :: forall scb sg (vibs :: [(*, Rate)]) (vias :: [(Nat, *)])
(slbtss :: (*, [(*, [BindingType])], [*])) a.
C scb
-> BindPoint
-> G sg vibs vias slbtss
-> (forall sgb. GBinded sgb vibs slbtss -> IO a)
-> IO a
bindPipelineGraphics (CommandBuffer.T.C C
c) BindPoint
bp (Pipeline.G G
g) forall sgb. GBinded sgb vibs slbtss -> IO a
f =
C -> BindPoint -> G -> IO ()
M.bindPipelineGraphics C
c BindPoint
bp G
g IO () -> IO a -> IO a
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> GBinded Any vibs slbtss -> IO a
forall sgb. GBinded sgb vibs slbtss -> IO a
f (C -> GBinded Any vibs slbtss
forall s (vibs :: [(*, Rate)])
(largs :: (*, [(*, [BindingType])], [*])).
C -> GBinded s vibs largs
CommandBuffer.T.GBinded C
c)
bindPipelineCompute :: CommandBuffer.C scmdb -> Pipeline.BindPoint ->
Pipeline.Compute.C scp slbtss ->
(forall scbnd . CommandBuffer.CBinded scbnd slbtss -> IO a) -> IO a
bindPipelineCompute :: forall {k} scmdb (scp :: k)
(slbtss :: (*, [(*, [BindingType])], [*])) a.
C scmdb
-> BindPoint
-> C scp slbtss
-> (forall scbnd. CBinded scbnd slbtss -> IO a)
-> IO a
bindPipelineCompute (CommandBuffer.T.C C
cb) BindPoint
bp (Pipeline.Compute.C C
g) forall scbnd. CBinded scbnd slbtss -> IO a
f =
C -> BindPoint -> C -> IO ()
M.bindPipelineCompute C
cb BindPoint
bp C
g IO () -> IO a -> IO a
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> CBinded Any slbtss -> IO a
forall scbnd. CBinded scbnd slbtss -> IO a
f (C -> CBinded Any slbtss
forall s (largs :: (*, [(*, [BindingType])], [*])).
C -> CBinded s largs
CommandBuffer.T.CBinded C
cb)
draw :: CommandBuffer.GBinded sc vibs slbtss ->
VertexCount -> InstanceCount -> FirstVertex -> FirstInstance -> IO ()
draw :: forall sc (vibs :: [(*, Rate)])
(slbtss :: (*, [(*, [BindingType])], [*])).
GBinded sc vibs slbtss
-> VertexCount
-> VertexCount
-> VertexCount
-> VertexCount
-> IO ()
draw (CommandBuffer.T.GBinded C
cb) VertexCount
vc VertexCount
ic VertexCount
fv VertexCount
fi = C
-> VertexCount
-> VertexCount
-> VertexCount
-> VertexCount
-> IO ()
M.draw C
cb VertexCount
vc VertexCount
ic VertexCount
fv VertexCount
fi
type VertexCount = Word32
type InstanceCount = Word32
type FirstVertex = Word32
type FirstInstance = Word32
drawIndexed :: CommandBuffer.GBinded sc vibs slbtss ->
IndexCount -> InstanceCount ->
FirstIndex -> VertexOffset -> FirstInstance -> IO ()
drawIndexed :: forall sc (vibs :: [(*, Rate)])
(slbtss :: (*, [(*, [BindingType])], [*])).
GBinded sc vibs slbtss
-> VertexCount
-> VertexCount
-> VertexCount
-> VertexOffset
-> VertexCount
-> IO ()
drawIndexed (CommandBuffer.T.GBinded C
cb) VertexCount
idxc VertexCount
istc VertexCount
fidx VertexOffset
vo VertexCount
fist =
C
-> VertexCount
-> VertexCount
-> VertexCount
-> VertexOffset
-> VertexCount
-> IO ()
M.drawIndexed C
cb VertexCount
idxc VertexCount
istc VertexCount
fidx VertexOffset
vo VertexCount
fist
type IndexCount = Word32
type FirstIndex = Word32
type VertexOffset = Int32
dispatch :: CommandBuffer.CBinded sc slbtss ->
GroupCountX -> GroupCountY -> GroupCountZ -> IO ()
dispatch :: forall sc (slbtss :: (*, [(*, [BindingType])], [*])).
CBinded sc slbtss
-> VertexCount -> VertexCount -> VertexCount -> IO ()
dispatch (CommandBuffer.T.CBinded C
cb) = C -> VertexCount -> VertexCount -> VertexCount -> IO ()
M.dispatch C
cb
type GroupCountX = Word32
type GroupCountY = Word32
type GroupCountZ = Word32
bindDescriptorSetsGraphics :: forall sgbnd vibs sl dsls pcs dss dsls' dyns . (
TMapIndex.M1_2 dss ~ dsls',
LayoutArgListOnlyDynamics dsls' ~ dyns,
InfixIndex dsls' dsls, GetDynamicLength dss,
HeteroParList.ZipListWithC3 KObj.SizeAlignment dyns ) =>
CommandBuffer.GBinded sgbnd vibs '(sl, dsls, pcs) ->
Pipeline.BindPoint -> PipelineLayout.P sl dsls pcs ->
HeteroParList.PL (U2 DescriptorSet.D) dss ->
HeteroParList.PL3 DynamicIndex dyns -> IO ()
bindDescriptorSetsGraphics :: forall sgbnd (vibs :: [(*, Rate)]) sl
(dsls :: [(*, [BindingType])]) (pcs :: [*])
(dss :: [(*, (*, [BindingType]))]) (dsls' :: [(*, [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 ()
bindDescriptorSetsGraphics
(CommandBuffer.T.GBinded C
c) BindPoint
bp (PipelineLayout.P P
l) PL (U2 D) dss
dss PL3 DynamicIndex dyns
idxs = do
lns <- PL (U2 D) dss
-> IO (PL3 Length (LayoutArgListOnlyDynamics (M1_2 dss)))
forall (sspslbtss :: [(*, (*, [BindingType]))]).
GetDynamicLength sspslbtss =>
PL (U2 D) sspslbtss
-> IO (PL3 Length (LayoutArgListOnlyDynamics (M1_2 sspslbtss)))
getDynamicLength PL (U2 D) dss
dss
let dosts = [[VertexCount]] -> [VertexCount]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[VertexCount]] -> [VertexCount])
-> [[VertexCount]] -> [VertexCount]
forall a b. (a -> b) -> a -> b
$ [[VertexCount]] -> [VertexCount]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[VertexCount]] -> [VertexCount])
-> [[[VertexCount]]] -> [[VertexCount]]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> PL3 Length dyns -> PL3 DynamicIndex dyns -> [[[VertexCount]]]
forall (osss :: [[[O]]]).
ZipListWithC3 SizeAlignment osss =>
PL3 Length osss -> PL3 DynamicIndex osss -> [[[VertexCount]]]
getOffsetListNew PL3 Length dyns
lns PL3 DynamicIndex dyns
idxs
M.bindDescriptorSets c bp l
(fromIntegral $ infixIndex @_ @dsls' @dsls)
(HeteroParList.toList
(\(U2 (DescriptorSet.D IORef (PL2 Length (BindingTypeListBufferOnlyDynamics (I1_2 s2)))
_ D
s)) -> D
s)
dss)
dosts
bindDescriptorSetsCompute :: forall scbnd sl dsls pcs dss dsls' dyns . (
TMapIndex.M1_2 dss ~ dsls',
LayoutArgListOnlyDynamics dsls' ~ dyns,
InfixIndex dsls' dsls, GetDynamicLength dss,
HeteroParList.ZipListWithC3 KObj.SizeAlignment dyns ) =>
CommandBuffer.CBinded scbnd '(sl, dsls, pcs) ->
PipelineLayout.P sl dsls pcs ->
HeteroParList.PL (U2 DescriptorSet.D) dss ->
HeteroParList.PL3 DynamicIndex dyns -> IO ()
bindDescriptorSetsCompute :: forall scbnd sl (dsls :: [(*, [BindingType])]) (pcs :: [*])
(dss :: [(*, (*, [BindingType]))]) (dsls' :: [(*, [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 ()
bindDescriptorSetsCompute
(CommandBuffer.T.CBinded C
c) (PipelineLayout.P P
l) PL (U2 D) dss
dss PL3 DynamicIndex dyns
idxs = do
lns <- PL (U2 D) dss
-> IO (PL3 Length (LayoutArgListOnlyDynamics (M1_2 dss)))
forall (sspslbtss :: [(*, (*, [BindingType]))]).
GetDynamicLength sspslbtss =>
PL (U2 D) sspslbtss
-> IO (PL3 Length (LayoutArgListOnlyDynamics (M1_2 sspslbtss)))
getDynamicLength PL (U2 D) dss
dss
let dosts = [[VertexCount]] -> [VertexCount]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[VertexCount]] -> [VertexCount])
-> [[VertexCount]] -> [VertexCount]
forall a b. (a -> b) -> a -> b
$ [[VertexCount]] -> [VertexCount]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[VertexCount]] -> [VertexCount])
-> [[[VertexCount]]] -> [[VertexCount]]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> PL3 Length dyns -> PL3 DynamicIndex dyns -> [[[VertexCount]]]
forall (osss :: [[[O]]]).
ZipListWithC3 SizeAlignment osss =>
PL3 Length osss -> PL3 DynamicIndex osss -> [[[VertexCount]]]
getOffsetListNew PL3 Length dyns
lns PL3 DynamicIndex dyns
idxs
M.bindDescriptorSets c Pipeline.BindPointCompute l
(fromIntegral $ infixIndex @_ @dsls' @dsls)
(HeteroParList.toList (\(U2 (DescriptorSet.D IORef (PL2 Length (BindingTypeListBufferOnlyDynamics (I1_2 s2)))
_ D
s)) -> D
s)
dss)
dosts
newtype DynamicIndex (obj :: KObj.O) = DynamicIndex Word32 deriving Int -> DynamicIndex obj -> ShowS
[DynamicIndex obj] -> ShowS
DynamicIndex obj -> String
(Int -> DynamicIndex obj -> ShowS)
-> (DynamicIndex obj -> String)
-> ([DynamicIndex obj] -> ShowS)
-> Show (DynamicIndex obj)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall (obj :: O). Int -> DynamicIndex obj -> ShowS
forall (obj :: O). [DynamicIndex obj] -> ShowS
forall (obj :: O). DynamicIndex obj -> String
$cshowsPrec :: forall (obj :: O). Int -> DynamicIndex obj -> ShowS
showsPrec :: Int -> DynamicIndex obj -> ShowS
$cshow :: forall (obj :: O). DynamicIndex obj -> String
show :: DynamicIndex obj -> String
$cshowList :: forall (obj :: O). [DynamicIndex obj] -> ShowS
showList :: [DynamicIndex obj] -> ShowS
Show
newtype DynamicOffset (obj :: KObj.O) = DynamicOffset Word32 deriving Int -> DynamicOffset obj -> ShowS
[DynamicOffset obj] -> ShowS
DynamicOffset obj -> String
(Int -> DynamicOffset obj -> ShowS)
-> (DynamicOffset obj -> String)
-> ([DynamicOffset obj] -> ShowS)
-> Show (DynamicOffset obj)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall (obj :: O). Int -> DynamicOffset obj -> ShowS
forall (obj :: O). [DynamicOffset obj] -> ShowS
forall (obj :: O). DynamicOffset obj -> String
$cshowsPrec :: forall (obj :: O). Int -> DynamicOffset obj -> ShowS
showsPrec :: Int -> DynamicOffset obj -> ShowS
$cshow :: forall (obj :: O). DynamicOffset obj -> String
show :: DynamicOffset obj -> String
$cshowList :: forall (obj :: O). [DynamicOffset obj] -> ShowS
showList :: [DynamicOffset obj] -> ShowS
Show
getOffset' :: forall obj . KObj.SizeAlignment obj =>
KObj.Length obj -> DynamicIndex obj -> Word32
getOffset' :: forall (obj :: O).
SizeAlignment obj =>
Length obj -> DynamicIndex obj -> VertexCount
getOffset' Length obj
ln (DynamicIndex VertexCount
i) = Size -> VertexCount
forall a b. (Integral a, Num b) => a -> b
fromIntegral Size
sz VertexCount -> VertexCount -> VertexCount
forall a. Num a => a -> a -> a
* VertexCount
i
where
sz :: Size
sz = ((Length obj -> Size
forall (obj :: O). SizeAlignment obj => Length obj -> Size
KObj.size Length obj
ln Size -> Size -> Size
forall a. Num a => a -> a -> a
- Size
1) Size -> Size -> Size
forall a. Integral a => a -> a -> a
`div` Size
algn Size -> Size -> Size
forall a. Num a => a -> a -> a
+ Size
1) Size -> Size -> Size
forall a. Num a => a -> a -> a
* Size
algn
algn :: Size
algn = forall (obj :: O). SizeAlignment obj => Size
KObj.alignment @obj
getOffsetListNew :: HeteroParList.ZipListWithC3 KObj.SizeAlignment osss =>
HeteroParList.PL3 KObj.Length osss ->
HeteroParList.PL3 DynamicIndex osss -> [[[Word32]]]
getOffsetListNew :: forall (osss :: [[[O]]]).
ZipListWithC3 SizeAlignment osss =>
PL3 Length osss -> PL3 DynamicIndex osss -> [[[VertexCount]]]
getOffsetListNew = forall {k} (c :: k -> Constraint) (ssss :: [[[k]]]) (t :: k -> *)
(t' :: k -> *) a.
ZipListWithC3 c ssss =>
(forall (s :: k). c s => t s -> t' s -> a)
-> PL3 t ssss -> PL3 t' ssss -> [[[a]]]
forall (c :: O -> Constraint) (ssss :: [[[O]]]) (t :: O -> *)
(t' :: O -> *) a.
ZipListWithC3 c ssss =>
(forall (s :: O). c s => t s -> t' s -> a)
-> PL3 t ssss -> PL3 t' ssss -> [[[a]]]
HeteroParList.zipListWithC3 @KObj.SizeAlignment Length s -> DynamicIndex s -> VertexCount
forall (obj :: O).
SizeAlignment obj =>
Length obj -> DynamicIndex obj -> VertexCount
getOffset'
class GetDynamicLength sspslbtss where
getDynamicLength ::
HeteroParList.PL (U2 DescriptorSet.D) sspslbtss ->
IO (HeteroParList.PL3 KObj.Length
(LayoutArgListOnlyDynamics (TMapIndex.M1_2 sspslbtss)))
type family LayoutArgListOnlyDynamics las where
LayoutArgListOnlyDynamics '[] = '[]
LayoutArgListOnlyDynamics (la ': las) =
Layout.BindingTypeListBufferOnlyDynamics (TIndex.I1_2 la) ':
LayoutArgListOnlyDynamics las
instance GetDynamicLength '[] where
getDynamicLength :: PL (U2 D) '[]
-> IO (PL3 Length (LayoutArgListOnlyDynamics (M1_2 '[])))
getDynamicLength PL (U2 D) '[]
HeteroParList.Nil = PL (PL2 Length) '[] -> IO (PL (PL2 Length) '[])
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure PL (PL2 Length) '[]
forall {k} (t :: k -> *). PL t '[]
HeteroParList.Nil
instance GetDynamicLength spslbtss =>
GetDynamicLength (slbts ': spslbtss) where
getDynamicLength :: PL (U2 D) (slbts : spslbtss)
-> IO
(PL3 Length (LayoutArgListOnlyDynamics (M1_2 (slbts : spslbtss))))
getDynamicLength (U2 D s1 s2
ds :** PL (U2 D) ss1
dss) =
PL (PL Length) (BindingTypeListBufferOnlyDynamics (I1_2 s2))
-> PL (PL2 Length) (LayoutArgListOnlyDynamics (M1_2 spslbtss))
-> PL
(PL2 Length)
(BindingTypeListBufferOnlyDynamics (I1_2 s2)
: LayoutArgListOnlyDynamics (M1_2 spslbtss))
forall {k} (t :: k -> *) (s :: k) (ss1 :: [k]).
t s -> PL t ss1 -> PL t (s : ss1)
(:**) (PL (PL Length) (BindingTypeListBufferOnlyDynamics (I1_2 s2))
-> PL (PL2 Length) (LayoutArgListOnlyDynamics (M1_2 spslbtss))
-> PL
(PL2 Length)
(BindingTypeListBufferOnlyDynamics (I1_2 s2)
: LayoutArgListOnlyDynamics (M1_2 spslbtss)))
-> IO
(PL (PL Length) (BindingTypeListBufferOnlyDynamics (I1_2 s2)))
-> IO
(PL (PL2 Length) (LayoutArgListOnlyDynamics (M1_2 spslbtss))
-> PL
(PL2 Length)
(BindingTypeListBufferOnlyDynamics (I1_2 s2)
: LayoutArgListOnlyDynamics (M1_2 spslbtss)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> D s1 s2
-> IO
(PL (PL Length) (BindingTypeListBufferOnlyDynamics (I1_2 s2)))
forall s (slbts :: (*, [BindingType])).
D s slbts
-> IO (PL2 Length (BindingTypeListBufferOnlyDynamics (I1_2 slbts)))
getDscSetLengthsNew D s1 s2
ds IO
(PL (PL2 Length) (LayoutArgListOnlyDynamics (M1_2 spslbtss))
-> PL
(PL2 Length)
(BindingTypeListBufferOnlyDynamics (I1_2 s2)
: LayoutArgListOnlyDynamics (M1_2 spslbtss)))
-> IO (PL (PL2 Length) (LayoutArgListOnlyDynamics (M1_2 spslbtss)))
-> IO
(PL
(PL2 Length)
(BindingTypeListBufferOnlyDynamics (I1_2 s2)
: LayoutArgListOnlyDynamics (M1_2 spslbtss)))
forall a b. IO (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> PL (U2 D) ss1
-> IO (PL3 Length (LayoutArgListOnlyDynamics (M1_2 ss1)))
forall (sspslbtss :: [(*, (*, [BindingType]))]).
GetDynamicLength sspslbtss =>
PL (U2 D) sspslbtss
-> IO (PL3 Length (LayoutArgListOnlyDynamics (M1_2 sspslbtss)))
getDynamicLength PL (U2 D) ss1
dss
getDscSetLengthsNew :: DescriptorSet.D s slbts ->
IO (HeteroParList.PL2 KObj.Length
(Layout.BindingTypeListBufferOnlyDynamics (TIndex.I1_2 slbts)))
getDscSetLengthsNew :: forall s (slbts :: (*, [BindingType])).
D s slbts
-> IO (PL2 Length (BindingTypeListBufferOnlyDynamics (I1_2 slbts)))
getDscSetLengthsNew (DescriptorSet.D IORef (PL2 Length (BindingTypeListBufferOnlyDynamics (I1_2 slbts)))
lns D
_) = IORef (PL2 Length (BindingTypeListBufferOnlyDynamics (I1_2 slbts)))
-> IO (PL2 Length (BindingTypeListBufferOnlyDynamics (I1_2 slbts)))
forall a. IORef a -> IO a
readIORef IORef (PL2 Length (BindingTypeListBufferOnlyDynamics (I1_2 slbts)))
lns
bindVertexBuffers :: forall sg vibs slbtss smsbnmts .
InfixIndex (TMapIndex.M3_5 smsbnmts) (TMapIndex.M0_2 vibs) =>
CommandBuffer.GBinded sg vibs slbtss ->
HeteroParList.PL (U5 Bffr.IndexedForList) smsbnmts -> IO ()
bindVertexBuffers :: forall sg (vibs :: [(*, Rate)])
(slbtss :: (*, [(*, [BindingType])], [*]))
(smsbnmts :: [(*, *, Symbol, *, Symbol)]).
InfixIndex (M3_5 smsbnmts) (M0_2 vibs) =>
GBinded sg vibs slbtss -> PL (U5 IndexedForList) smsbnmts -> IO ()
bindVertexBuffers (CommandBuffer.T.GBinded C
cb) PL (U5 IndexedForList) smsbnmts
bils = C -> VertexCount -> [(B, Size)] -> IO ()
M.bindVertexBuffers
C
cb (Int -> VertexCount
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
fb) (PL (U5 IndexedForList) smsbnmts -> [(B, Size)]
forall {k3} (smsbvs :: [(*, *, Symbol, k3, Symbol)]).
PL (U5 IndexedForList) smsbvs -> [(B, Size)]
Bffr.I.indexedListToMiddles PL (U5 IndexedForList) smsbnmts
bils)
where fb :: Int
fb = forall k (xs :: [k]) (ys :: [k]). InfixIndex xs ys => Int
infixIndex @_ @(TMapIndex.M3_5 smsbnmts) @(TMapIndex.M0_2 vibs)
bindIndexBuffer :: forall sg vibs slbtss sm sb nm i onm . IsIndex i =>
CommandBuffer.GBinded sg vibs slbtss ->
Bffr.IndexedForList sm sb nm i onm -> IO ()
bindIndexBuffer :: forall {k} sg (vibs :: [(*, Rate)])
(slbtss :: (*, [(*, [BindingType])], [*])) sm sb (nm :: Symbol)
(i :: k) (onm :: Symbol).
IsIndex i =>
GBinded sg vibs slbtss -> IndexedForList sm sb nm i onm -> IO ()
bindIndexBuffer (CommandBuffer.T.GBinded C
cb) IndexedForList sm sb nm i onm
ib =
(B -> Size -> IndexType -> IO ())
-> (B, Size) -> IndexType -> IO ()
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry (C -> B -> Size -> IndexType -> IO ()
M.bindIndexBuffer C
cb) (IndexedForList sm sb nm i onm -> (B, Size)
forall {k} sm sb (nm :: Symbol) (v :: k) (onm :: Symbol).
IndexedForList sm sb nm v onm -> (B, Size)
Bffr.I.indexedListToMiddle IndexedForList sm sb nm i onm
ib) (forall (a :: k). IsIndex a => IndexType
forall {k} (a :: k). IsIndex a => IndexType
indexType @i)
class IsIndex a where indexType :: IndexType
instance IsIndex Word16 where indexType :: IndexType
indexType = IndexType
IndexTypeUint16
instance IsIndex Word32 where indexType :: IndexType
indexType = IndexType
IndexTypeUint32
copyBuffer :: forall cpobjss scb sms sbs nms objss smd sbd nmd objsd .
Bffr.MakeCopies cpobjss objss objsd => CommandBuffer.C scb ->
Bffr.Binded sms sbs nms objss -> Bffr.Binded smd sbd nmd objsd -> IO ()
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 ()
copyBuffer (CommandBuffer.T.C C
cb) (Bffr.Binded PL Length objss
lnss B
s) (Bffr.Binded PL Length objsd
lnsd B
d) =
C -> B -> B -> [Copy] -> IO ()
M.copyBuffer C
cb B
s B
d (forall (cpss :: [([O], Nat, Nat)]) (ss :: [O]) (ds :: [O]).
MakeCopies cpss ss ds =>
PL Length ss -> PL Length ds -> [Copy]
Bffr.I.makeCopies @cpobjss PL Length objss
lnss PL Length objsd
lnsd)
pushConstantsGraphics :: forall sss sc vibs sl sbtss pcs ts . (
T.ShaderStageFlagBitsListToValue sss,
PokableList ts, InfixOffsetSize ts pcs ) =>
CommandBuffer.GBinded sc vibs '(sl, sbtss, pcs) ->
PipelineLayout.P sl sbtss pcs -> HeteroParList.L ts -> IO ()
pushConstantsGraphics :: forall (sss :: [ShaderStageFlagBits]) sc (vibs :: [(*, Rate)]) sl
(sbtss :: [(*, [BindingType])]) (pcs :: [*]) (ts :: [*]).
(ShaderStageFlagBitsListToValue sss, PokableList ts,
InfixOffsetSize ts pcs) =>
GBinded sc vibs '(sl, sbtss, pcs)
-> P sl sbtss pcs -> L ts -> IO ()
pushConstantsGraphics (CommandBuffer.T.GBinded C
cb) (PipelineLayout.P P
lyt) L ts
xs =
C -> P -> ShaderStageFlags -> VertexCount -> L ts -> IO ()
forall (as :: [*]).
PokableList as =>
C -> P -> ShaderStageFlags -> VertexCount -> L as -> IO ()
M.pushConstants
C
cb P
lyt (forall (ts :: [ShaderStageFlagBits]).
ShaderStageFlagBitsListToValue ts =>
ShaderStageFlags
T.shaderStageFlagBitsListToValue @sss) VertexCount
offt L ts
xs
where (Int -> VertexCount
forall a b. (Integral a, Num b) => a -> b
fromIntegral -> VertexCount
offt, Int
_) = forall (part :: [*]) (whole :: [*]).
InfixOffsetSize part whole =>
(Int, Int)
infixOffsetSize @ts @pcs
pushConstantsCompute :: forall sss sc sl sbtss pcs ts . (
T.ShaderStageFlagBitsListToValue sss,
PokableList ts, InfixOffsetSize ts pcs ) =>
CommandBuffer.CBinded sc '(sl, sbtss, pcs) ->
PipelineLayout.P sl sbtss pcs -> HeteroParList.L ts -> IO ()
pushConstantsCompute :: forall (sss :: [ShaderStageFlagBits]) sc sl
(sbtss :: [(*, [BindingType])]) (pcs :: [*]) (ts :: [*]).
(ShaderStageFlagBitsListToValue sss, PokableList ts,
InfixOffsetSize ts pcs) =>
CBinded sc '(sl, sbtss, pcs) -> P sl sbtss pcs -> L ts -> IO ()
pushConstantsCompute (CommandBuffer.T.CBinded C
cb) (PipelineLayout.P P
lyt) L ts
xs =
C -> P -> ShaderStageFlags -> VertexCount -> L ts -> IO ()
forall (as :: [*]).
PokableList as =>
C -> P -> ShaderStageFlags -> VertexCount -> L as -> IO ()
M.pushConstants
C
cb P
lyt (forall (ts :: [ShaderStageFlagBits]).
ShaderStageFlagBitsListToValue ts =>
ShaderStageFlags
T.shaderStageFlagBitsListToValue @sss) VertexCount
offt L ts
xs
where (Int -> VertexCount
forall a b. (Integral a, Num b) => a -> b
fromIntegral -> VertexCount
offt, Int
_) = forall (part :: [*]) (whole :: [*]).
InfixOffsetSize part whole =>
(Int, Int)
infixOffsetSize @ts @pcs
pipelineBarrier :: (
HeteroParList.ToListWithCCpsM' WithPoked TMaybe.M mbargs,
HeteroParList.ToListWithCCpsM' WithPoked TMaybe.M
(TMapIndex.M0_5 bmbargss),
HeteroParList.ToListWithCCpsM' WithPoked TMaybe.M
(TMapIndex.M0_5 imbargss),
Bffr.MemoryBarrierListToMiddle bmbargss,
Image.MemoryBarrierListToMiddle imbargss ) =>
CommandBuffer.C scb -> Pipeline.StageFlags -> Pipeline.StageFlags ->
DependencyFlags -> HeteroParList.PL Memory.Barrier mbargs ->
HeteroParList.PL (U5 Bffr.MemoryBarrier) bmbargss ->
HeteroParList.PL (U5 Image.MemoryBarrier) imbargss -> IO ()
pipelineBarrier :: forall (mbargs :: [Maybe (*)])
(bmbargss :: [(Maybe (*), *, *, Symbol, O)])
(imbargss :: [(Maybe (*), *, *, 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 ()
pipelineBarrier (CommandBuffer.T.C C
cb) StageFlags
ssm StageFlags
dsm DependencyFlags
dfs PL Barrier mbargs
mbs PL (U5 MemoryBarrier) bmbargss
bmbs PL (U5 MemoryBarrier) imbargss
imbs =
C
-> StageFlags
-> StageFlags
-> DependencyFlags
-> PL Barrier mbargs
-> PL MemoryBarrier (M0_5 bmbargss)
-> PL MemoryBarrier (M0_5 imbargss)
-> IO ()
forall (ns :: [Maybe (*)]) (ns' :: [Maybe (*)])
(ns'' :: [Maybe (*)]).
(ToListWithCCpsM' WithPoked M ns, ToListWithCCpsM' WithPoked M ns',
ToListWithCCpsM' WithPoked M ns'') =>
C
-> StageFlags
-> StageFlags
-> DependencyFlags
-> PL Barrier ns
-> PL MemoryBarrier ns'
-> PL MemoryBarrier ns''
-> IO ()
M.pipelineBarrier C
cb StageFlags
ssm StageFlags
dsm DependencyFlags
dfs PL Barrier mbargs
mbs
(PL (U5 MemoryBarrier) bmbargss -> PL MemoryBarrier (M0_5 bmbargss)
forall (nsmsbnmobjs :: [(Maybe (*), *, *, Symbol, O)]).
MemoryBarrierListToMiddle nsmsbnmobjs =>
PL (U5 MemoryBarrier) nsmsbnmobjs
-> PL MemoryBarrier (M0_5 nsmsbnmobjs)
Bffr.I.memoryBarrierListToMiddle PL (U5 MemoryBarrier) bmbargss
bmbs)
(PL (U5 MemoryBarrier) imbargss -> PL MemoryBarrier (M0_5 imbargss)
forall (mbargs :: [(Maybe (*), *, *, Symbol, Format)]).
MemoryBarrierListToMiddle mbargs =>
PL (U5 MemoryBarrier) mbargs -> PL MemoryBarrier (M0_5 mbargs)
Image.I.memoryBarrierListToMiddle PL (U5 MemoryBarrier) imbargss
imbs)
pipelineBarrier2 :: (
WithPoked (TMaybe.M mn),
HPList.ToListWithCCpsM' WithPoked TMaybe.M mbas, Length mbas,
HPList.ToListWithCCpsM' WithPoked TMaybe.M (TMapIndex.M0_5 bmbas),
Length (TMapIndex.M0_5 bmbas),
HPList.ToListWithCCpsM' WithPoked TMaybe.M (TMapIndex.M0_5 imbas),
Length (TMapIndex.M0_5 imbas),
Bffr.I.MemoryBarrier2ListToMiddle bmbas,
Image.I.MemoryBarrier2ListToMiddle imbas ) =>
CommandBuffer.C scb -> DependencyInfo mn mbas bmbas imbas -> IO ()
pipelineBarrier2 :: forall (mn :: Maybe (*)) (mbas :: [Maybe (*)])
(bmbas :: [(Maybe (*), *, *, Symbol, O)])
(imbas :: [(Maybe (*), *, *, 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 ()
pipelineBarrier2 (CommandBuffer.T.C C
cb) DependencyInfo mn mbas bmbas imbas
di =
C -> DependencyInfo mn mbas (M0_5 bmbas) (M0_5 imbas) -> IO ()
forall (mn :: Maybe (*)) (mbas :: [Maybe (*)])
(bmbas :: [Maybe (*)]) (imbas :: [Maybe (*)]).
(WithPoked (M mn), ToListWithCCpsM' WithPoked M mbas, Length mbas,
ToListWithCCpsM' WithPoked M bmbas, Length bmbas,
ToListWithCCpsM' WithPoked M imbas, Length imbas) =>
C -> DependencyInfo mn mbas bmbas imbas -> IO ()
M.pipelineBarrier2 C
cb (DependencyInfo mn mbas (M0_5 bmbas) (M0_5 imbas) -> IO ())
-> DependencyInfo mn mbas (M0_5 bmbas) (M0_5 imbas) -> IO ()
forall a b. (a -> b) -> a -> b
$ DependencyInfo mn mbas bmbas imbas
-> DependencyInfo mn mbas (M0_5 bmbas) (M0_5 imbas)
forall (bmbas :: [(Maybe (*), *, *, Symbol, O)])
(imbas :: [(Maybe (*), *, *, Symbol, Format)]) (mn :: Maybe (*))
(mbas :: [Maybe (*)]).
(MemoryBarrier2ListToMiddle bmbas,
MemoryBarrier2ListToMiddle imbas) =>
DependencyInfo mn mbas bmbas imbas
-> DependencyInfo mn mbas (M0_5 bmbas) (M0_5 imbas)
dependencyInfoToMiddle DependencyInfo mn mbas bmbas imbas
di
copyBufferToImage ::
forall (algn :: Nat) img inms scb smb sbb bnm objs smi si inm .
(Bffr.ImageCopyListToMiddle algn objs img inms) =>
CommandBuffer.C scb -> Bffr.Binded smb sbb bnm objs ->
Image.Binded smi si inm (KObj.ImageFormat img) -> Image.Layout ->
HeteroParList.PL (Bffr.ImageCopy img) inms -> IO ()
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) inms
-> IO ()
copyBufferToImage (CommandBuffer.T.C C
cb)
bf :: Binded smb sbb bnm objs
bf@(Bffr.Binded PL Length objs
_ B
mbf) (Image.Binded I
mim) Layout
imlyt PL (ImageCopy img) inms
ics =
C -> B -> I -> Layout -> [ImageCopy] -> IO ()
M.copyBufferToImage C
cb B
mbf I
mim Layout
imlyt [ImageCopy]
mics
where mics :: [ImageCopy]
mics = forall (algn :: Nat) (objs :: [O]) img (inms :: [Symbol]) sm sb
(nm :: Symbol).
ImageCopyListToMiddle algn objs img inms =>
Binded sm sb nm objs -> PL (ImageCopy img) inms -> [ImageCopy]
forall {k} (algn :: k) (objs :: [O]) img (inms :: [Symbol]) sm sb
(nm :: Symbol).
ImageCopyListToMiddle algn objs img inms =>
Binded sm sb nm objs -> PL (ImageCopy img) inms -> [ImageCopy]
Bffr.I.imageCopyListToMiddle @algn Binded smb sbb bnm objs
bf PL (ImageCopy img) inms
ics
copyImageToBuffer ::
forall (algn :: Nat) img inms scb smi si inm smb sbb bnm objs .
(Bffr.ImageCopyListToMiddle algn objs img inms) =>
CommandBuffer.C scb ->
Image.Binded smi si inm (KObj.ImageFormat img) -> Image.Layout ->
Bffr.Binded smb sbb bnm objs ->
HeteroParList.PL (Bffr.ImageCopy img) inms -> IO ()
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) inms
-> IO ()
copyImageToBuffer (CommandBuffer.T.C C
cb)
(Image.Binded I
mim) Layout
imlyt bf :: Binded smb sbb bnm objs
bf@(Bffr.Binded PL Length objs
_ B
mbf) PL (ImageCopy img) inms
ics =
C -> I -> Layout -> B -> [ImageCopy] -> IO ()
M.copyImageToBuffer C
cb I
mim Layout
imlyt B
mbf [ImageCopy]
mics
where mics :: [ImageCopy]
mics = forall (algn :: Nat) (objs :: [O]) img (inms :: [Symbol]) sm sb
(nm :: Symbol).
ImageCopyListToMiddle algn objs img inms =>
Binded sm sb nm objs -> PL (ImageCopy img) inms -> [ImageCopy]
forall {k} (algn :: k) (objs :: [O]) img (inms :: [Symbol]) sm sb
(nm :: Symbol).
ImageCopyListToMiddle algn objs img inms =>
Binded sm sb nm objs -> PL (ImageCopy img) inms -> [ImageCopy]
Bffr.I.imageCopyListToMiddle @algn Binded smb sbb bnm objs
bf PL (ImageCopy img) inms
ics
blitImage :: CommandBuffer.C scb ->
Image.Binded sms sis nms fmts -> Image.Layout ->
Image.Binded smd sid nmd fmtd -> Image.Layout ->
[Image.M.Blit] -> Filter -> IO ()
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 ()
blitImage (CommandBuffer.T.C C
cb)
(Image.Binded I
src) Layout
slyt (Image.Binded I
dst) Layout
dlyt [Blit]
blts Filter
fltr =
C -> I -> Layout -> I -> Layout -> [Blit] -> Filter -> IO ()
M.blitImage C
cb I
src Layout
slyt I
dst Layout
dlyt [Blit]
blts Filter
fltr
blitImage2 :: (
WithPoked (TMaybe.M mn),
Length ras, HPList.ToListWithCCpsM' WithPoked TMaybe.M ras ) =>
CommandBuffer.C scb ->
BlitImageInfo2 mn sms sis nms fmts smd sid nmd fmtd ras -> IO ()
blitImage2 :: forall (mn :: Maybe (*)) (ras :: [Maybe (*)]) 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 ()
blitImage2 (CommandBuffer.T.C C
cb) BlitImageInfo2 mn sms sis nms fmts smd sid nmd fmtd ras
bii =
C -> BlitImageInfo2 mn ras -> IO ()
forall (mn :: Maybe (*)) (ras :: [Maybe (*)]).
(WithPoked (M mn), Length ras, ToListWithCCpsM' WithPoked M ras) =>
C -> BlitImageInfo2 mn ras -> IO ()
M.blitImage2 C
cb (BlitImageInfo2 mn ras -> IO ()) -> BlitImageInfo2 mn ras -> IO ()
forall a b. (a -> b) -> a -> b
$ BlitImageInfo2 mn sms sis nms fmts smd sid nmd fmtd ras
-> BlitImageInfo2 mn ras
forall (mn :: Maybe (*)) sms sis (nms :: Symbol) (fmts :: Format)
smd sid (nmd :: Symbol) (fmtd :: Format) (ras :: [Maybe (*)]).
BlitImageInfo2 mn sms sis nms fmts smd sid nmd fmtd ras
-> BlitImageInfo2 mn ras
blitImageInfo2ToMiddle BlitImageInfo2 mn sms sis nms fmts smd sid nmd fmtd ras
bii
resetQueryPool :: CommandBuffer.C sc ->
QueryPool.Q sq tp -> Query.First -> Query.Count -> IO ()
resetQueryPool :: forall sc sq (tp :: Bool -> *).
C sc -> Q sq tp -> VertexCount -> VertexCount -> IO ()
resetQueryPool (CommandBuffer.T.C C
cb) (QueryPool.Q Q
qp) VertexCount
fq VertexCount
qc =
C -> Q -> VertexCount -> VertexCount -> IO ()
M.resetQueryPool C
cb Q
qp VertexCount
fq VertexCount
qc
beginQuery :: CommandBuffer.C sc ->
QueryPool.Q sq tp -> Query.Q -> Query.ControlFlags -> IO a -> IO ()
beginQuery :: forall sc sq (tp :: Bool -> *) a.
C sc -> Q sq tp -> VertexCount -> ControlFlags -> IO a -> IO ()
beginQuery (CommandBuffer.T.C C
cb) (QueryPool.Q Q
qp) VertexCount
i ControlFlags
flgs IO a
act =
C -> Q -> VertexCount -> ControlFlags -> IO ()
M.beginQuery C
cb Q
qp VertexCount
i ControlFlags
flgs IO () -> IO a -> IO a
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> IO a
act IO a -> IO () -> IO ()
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> C -> Q -> VertexCount -> IO ()
M.endQuery C
cb Q
qp VertexCount
i
writeTimestamp :: CommandBuffer.C sc -> Pipeline.StageFlagBits ->
QueryPool.Q sq QueryPool.Timestamp -> Query.Q -> IO ()
writeTimestamp :: forall sc sq.
C sc -> StageFlags -> Q sq Timestamp -> VertexCount -> IO ()
writeTimestamp (CommandBuffer.T.C C
cb) StageFlags
sflgs (QueryPool.Q Q
qp) VertexCount
i =
C -> StageFlags -> Q -> VertexCount -> IO ()
M.writeTimestamp C
cb StageFlags
sflgs Q
qp VertexCount
i
clearColorImage :: M.ClearColorValueToCore cct =>
CommandBuffer.C sc -> Image.Binded sm si nm fmt -> Image.Layout ->
ClearValue ('ClearTypeColor cct) -> [Image.SubresourceRange] -> IO ()
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 ()
clearColorImage (CommandBuffer.T.C C
cb) (Image.Binded I
img) Layout
lyt ClearValue ('ClearTypeColor cct)
cv [SubresourceRange]
srrs =
C
-> I
-> Layout
-> ClearValue ('ClearTypeColor cct)
-> [SubresourceRange]
-> IO ()
forall (cct :: ClearColorType).
ClearColorValueToCore cct =>
C
-> I
-> Layout
-> ClearValue ('ClearTypeColor cct)
-> [SubresourceRange]
-> IO ()
M.clearColorImage C
cb I
img Layout
lyt ClearValue ('ClearTypeColor cct)
cv [SubresourceRange]
srrs