module Resource.Model where

import RIO

import Codec.Serialise qualified as CBOR
import Data.List qualified as List
import Data.Vector.Storable qualified as Storable
import Foreign (Storable(..))
import Vulkan.Core10 qualified as Vk

import Engine.Vulkan.Types (HasVulkan(..), Queues(..))
import Resource.Buffer qualified as Buffer

data Indexed storage pos attrs = Indexed
  { Indexed storage pos attrs -> Allocated storage pos
iPositions :: Buffer.Allocated storage pos
  , Indexed storage pos attrs -> Allocated storage attrs
iAttrs     :: Buffer.Allocated storage attrs
  , Indexed storage pos attrs -> Allocated storage Word32
iIndices   :: Buffer.Allocated storage Word32
  } deriving (Int -> Indexed storage pos attrs -> ShowS
[Indexed storage pos attrs] -> ShowS
Indexed storage pos attrs -> String
(Int -> Indexed storage pos attrs -> ShowS)
-> (Indexed storage pos attrs -> String)
-> ([Indexed storage pos attrs] -> ShowS)
-> Show (Indexed storage pos attrs)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall (storage :: Store) pos attrs.
Int -> Indexed storage pos attrs -> ShowS
forall (storage :: Store) pos attrs.
[Indexed storage pos attrs] -> ShowS
forall (storage :: Store) pos attrs.
Indexed storage pos attrs -> String
showList :: [Indexed storage pos attrs] -> ShowS
$cshowList :: forall (storage :: Store) pos attrs.
[Indexed storage pos attrs] -> ShowS
show :: Indexed storage pos attrs -> String
$cshow :: forall (storage :: Store) pos attrs.
Indexed storage pos attrs -> String
showsPrec :: Int -> Indexed storage pos attrs -> ShowS
$cshowsPrec :: forall (storage :: Store) pos attrs.
Int -> Indexed storage pos attrs -> ShowS
Show)

data Vertex pos attrs = Vertex
  { Vertex pos attrs -> pos
vPosition :: pos
  , Vertex pos attrs -> attrs
vAttrs    :: attrs
  } deriving (Vertex pos attrs -> Vertex pos attrs -> Bool
(Vertex pos attrs -> Vertex pos attrs -> Bool)
-> (Vertex pos attrs -> Vertex pos attrs -> Bool)
-> Eq (Vertex pos attrs)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall pos attrs.
(Eq pos, Eq attrs) =>
Vertex pos attrs -> Vertex pos attrs -> Bool
/= :: Vertex pos attrs -> Vertex pos attrs -> Bool
$c/= :: forall pos attrs.
(Eq pos, Eq attrs) =>
Vertex pos attrs -> Vertex pos attrs -> Bool
== :: Vertex pos attrs -> Vertex pos attrs -> Bool
$c== :: forall pos attrs.
(Eq pos, Eq attrs) =>
Vertex pos attrs -> Vertex pos attrs -> Bool
Eq, Eq (Vertex pos attrs)
Eq (Vertex pos attrs)
-> (Vertex pos attrs -> Vertex pos attrs -> Ordering)
-> (Vertex pos attrs -> Vertex pos attrs -> Bool)
-> (Vertex pos attrs -> Vertex pos attrs -> Bool)
-> (Vertex pos attrs -> Vertex pos attrs -> Bool)
-> (Vertex pos attrs -> Vertex pos attrs -> Bool)
-> (Vertex pos attrs -> Vertex pos attrs -> Vertex pos attrs)
-> (Vertex pos attrs -> Vertex pos attrs -> Vertex pos attrs)
-> Ord (Vertex pos attrs)
Vertex pos attrs -> Vertex pos attrs -> Bool
Vertex pos attrs -> Vertex pos attrs -> Ordering
Vertex pos attrs -> Vertex pos attrs -> Vertex pos attrs
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall pos attrs. (Ord pos, Ord attrs) => Eq (Vertex pos attrs)
forall pos attrs.
(Ord pos, Ord attrs) =>
Vertex pos attrs -> Vertex pos attrs -> Bool
forall pos attrs.
(Ord pos, Ord attrs) =>
Vertex pos attrs -> Vertex pos attrs -> Ordering
forall pos attrs.
(Ord pos, Ord attrs) =>
Vertex pos attrs -> Vertex pos attrs -> Vertex pos attrs
min :: Vertex pos attrs -> Vertex pos attrs -> Vertex pos attrs
$cmin :: forall pos attrs.
(Ord pos, Ord attrs) =>
Vertex pos attrs -> Vertex pos attrs -> Vertex pos attrs
max :: Vertex pos attrs -> Vertex pos attrs -> Vertex pos attrs
$cmax :: forall pos attrs.
(Ord pos, Ord attrs) =>
Vertex pos attrs -> Vertex pos attrs -> Vertex pos attrs
>= :: Vertex pos attrs -> Vertex pos attrs -> Bool
$c>= :: forall pos attrs.
(Ord pos, Ord attrs) =>
Vertex pos attrs -> Vertex pos attrs -> Bool
> :: Vertex pos attrs -> Vertex pos attrs -> Bool
$c> :: forall pos attrs.
(Ord pos, Ord attrs) =>
Vertex pos attrs -> Vertex pos attrs -> Bool
<= :: Vertex pos attrs -> Vertex pos attrs -> Bool
$c<= :: forall pos attrs.
(Ord pos, Ord attrs) =>
Vertex pos attrs -> Vertex pos attrs -> Bool
< :: Vertex pos attrs -> Vertex pos attrs -> Bool
$c< :: forall pos attrs.
(Ord pos, Ord attrs) =>
Vertex pos attrs -> Vertex pos attrs -> Bool
compare :: Vertex pos attrs -> Vertex pos attrs -> Ordering
$ccompare :: forall pos attrs.
(Ord pos, Ord attrs) =>
Vertex pos attrs -> Vertex pos attrs -> Ordering
$cp1Ord :: forall pos attrs. (Ord pos, Ord attrs) => Eq (Vertex pos attrs)
Ord, Int -> Vertex pos attrs -> ShowS
[Vertex pos attrs] -> ShowS
Vertex pos attrs -> String
(Int -> Vertex pos attrs -> ShowS)
-> (Vertex pos attrs -> String)
-> ([Vertex pos attrs] -> ShowS)
-> Show (Vertex pos attrs)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall pos attrs.
(Show pos, Show attrs) =>
Int -> Vertex pos attrs -> ShowS
forall pos attrs.
(Show pos, Show attrs) =>
[Vertex pos attrs] -> ShowS
forall pos attrs.
(Show pos, Show attrs) =>
Vertex pos attrs -> String
showList :: [Vertex pos attrs] -> ShowS
$cshowList :: forall pos attrs.
(Show pos, Show attrs) =>
[Vertex pos attrs] -> ShowS
show :: Vertex pos attrs -> String
$cshow :: forall pos attrs.
(Show pos, Show attrs) =>
Vertex pos attrs -> String
showsPrec :: Int -> Vertex pos attrs -> ShowS
$cshowsPrec :: forall pos attrs.
(Show pos, Show attrs) =>
Int -> Vertex pos attrs -> ShowS
Show, a -> Vertex pos b -> Vertex pos a
(a -> b) -> Vertex pos a -> Vertex pos b
(forall a b. (a -> b) -> Vertex pos a -> Vertex pos b)
-> (forall a b. a -> Vertex pos b -> Vertex pos a)
-> Functor (Vertex pos)
forall a b. a -> Vertex pos b -> Vertex pos a
forall a b. (a -> b) -> Vertex pos a -> Vertex pos b
forall pos a b. a -> Vertex pos b -> Vertex pos a
forall pos a b. (a -> b) -> Vertex pos a -> Vertex pos b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> Vertex pos b -> Vertex pos a
$c<$ :: forall pos a b. a -> Vertex pos b -> Vertex pos a
fmap :: (a -> b) -> Vertex pos a -> Vertex pos b
$cfmap :: forall pos a b. (a -> b) -> Vertex pos a -> Vertex pos b
Functor, Vertex pos a -> Bool
(a -> m) -> Vertex pos a -> m
(a -> b -> b) -> b -> Vertex pos a -> b
(forall m. Monoid m => Vertex pos m -> m)
-> (forall m a. Monoid m => (a -> m) -> Vertex pos a -> m)
-> (forall m a. Monoid m => (a -> m) -> Vertex pos a -> m)
-> (forall a b. (a -> b -> b) -> b -> Vertex pos a -> b)
-> (forall a b. (a -> b -> b) -> b -> Vertex pos a -> b)
-> (forall b a. (b -> a -> b) -> b -> Vertex pos a -> b)
-> (forall b a. (b -> a -> b) -> b -> Vertex pos a -> b)
-> (forall a. (a -> a -> a) -> Vertex pos a -> a)
-> (forall a. (a -> a -> a) -> Vertex pos a -> a)
-> (forall a. Vertex pos a -> [a])
-> (forall a. Vertex pos a -> Bool)
-> (forall a. Vertex pos a -> Int)
-> (forall a. Eq a => a -> Vertex pos a -> Bool)
-> (forall a. Ord a => Vertex pos a -> a)
-> (forall a. Ord a => Vertex pos a -> a)
-> (forall a. Num a => Vertex pos a -> a)
-> (forall a. Num a => Vertex pos a -> a)
-> Foldable (Vertex pos)
forall a. Eq a => a -> Vertex pos a -> Bool
forall a. Num a => Vertex pos a -> a
forall a. Ord a => Vertex pos a -> a
forall m. Monoid m => Vertex pos m -> m
forall a. Vertex pos a -> Bool
forall a. Vertex pos a -> Int
forall a. Vertex pos a -> [a]
forall a. (a -> a -> a) -> Vertex pos a -> a
forall pos a. Eq a => a -> Vertex pos a -> Bool
forall pos a. Num a => Vertex pos a -> a
forall pos a. Ord a => Vertex pos a -> a
forall m a. Monoid m => (a -> m) -> Vertex pos a -> m
forall pos m. Monoid m => Vertex pos m -> m
forall pos a. Vertex pos a -> Bool
forall pos a. Vertex pos a -> Int
forall pos a. Vertex pos a -> [a]
forall b a. (b -> a -> b) -> b -> Vertex pos a -> b
forall a b. (a -> b -> b) -> b -> Vertex pos a -> b
forall pos a. (a -> a -> a) -> Vertex pos a -> a
forall pos m a. Monoid m => (a -> m) -> Vertex pos a -> m
forall pos b a. (b -> a -> b) -> b -> Vertex pos a -> b
forall pos a b. (a -> b -> b) -> b -> Vertex pos a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: Vertex pos a -> a
$cproduct :: forall pos a. Num a => Vertex pos a -> a
sum :: Vertex pos a -> a
$csum :: forall pos a. Num a => Vertex pos a -> a
minimum :: Vertex pos a -> a
$cminimum :: forall pos a. Ord a => Vertex pos a -> a
maximum :: Vertex pos a -> a
$cmaximum :: forall pos a. Ord a => Vertex pos a -> a
elem :: a -> Vertex pos a -> Bool
$celem :: forall pos a. Eq a => a -> Vertex pos a -> Bool
length :: Vertex pos a -> Int
$clength :: forall pos a. Vertex pos a -> Int
null :: Vertex pos a -> Bool
$cnull :: forall pos a. Vertex pos a -> Bool
toList :: Vertex pos a -> [a]
$ctoList :: forall pos a. Vertex pos a -> [a]
foldl1 :: (a -> a -> a) -> Vertex pos a -> a
$cfoldl1 :: forall pos a. (a -> a -> a) -> Vertex pos a -> a
foldr1 :: (a -> a -> a) -> Vertex pos a -> a
$cfoldr1 :: forall pos a. (a -> a -> a) -> Vertex pos a -> a
foldl' :: (b -> a -> b) -> b -> Vertex pos a -> b
$cfoldl' :: forall pos b a. (b -> a -> b) -> b -> Vertex pos a -> b
foldl :: (b -> a -> b) -> b -> Vertex pos a -> b
$cfoldl :: forall pos b a. (b -> a -> b) -> b -> Vertex pos a -> b
foldr' :: (a -> b -> b) -> b -> Vertex pos a -> b
$cfoldr' :: forall pos a b. (a -> b -> b) -> b -> Vertex pos a -> b
foldr :: (a -> b -> b) -> b -> Vertex pos a -> b
$cfoldr :: forall pos a b. (a -> b -> b) -> b -> Vertex pos a -> b
foldMap' :: (a -> m) -> Vertex pos a -> m
$cfoldMap' :: forall pos m a. Monoid m => (a -> m) -> Vertex pos a -> m
foldMap :: (a -> m) -> Vertex pos a -> m
$cfoldMap :: forall pos m a. Monoid m => (a -> m) -> Vertex pos a -> m
fold :: Vertex pos m -> m
$cfold :: forall pos m. Monoid m => Vertex pos m -> m
Foldable, Functor (Vertex pos)
Foldable (Vertex pos)
Functor (Vertex pos)
-> Foldable (Vertex pos)
-> (forall (f :: * -> *) a b.
    Applicative f =>
    (a -> f b) -> Vertex pos a -> f (Vertex pos b))
-> (forall (f :: * -> *) a.
    Applicative f =>
    Vertex pos (f a) -> f (Vertex pos a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> Vertex pos a -> m (Vertex pos b))
-> (forall (m :: * -> *) a.
    Monad m =>
    Vertex pos (m a) -> m (Vertex pos a))
-> Traversable (Vertex pos)
(a -> f b) -> Vertex pos a -> f (Vertex pos b)
forall pos. Functor (Vertex pos)
forall pos. Foldable (Vertex pos)
forall pos (m :: * -> *) a.
Monad m =>
Vertex pos (m a) -> m (Vertex pos a)
forall pos (f :: * -> *) a.
Applicative f =>
Vertex pos (f a) -> f (Vertex pos a)
forall pos (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Vertex pos a -> m (Vertex pos b)
forall pos (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Vertex pos a -> f (Vertex pos b)
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
    Applicative f =>
    (a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a.
Monad m =>
Vertex pos (m a) -> m (Vertex pos a)
forall (f :: * -> *) a.
Applicative f =>
Vertex pos (f a) -> f (Vertex pos a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Vertex pos a -> m (Vertex pos b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Vertex pos a -> f (Vertex pos b)
sequence :: Vertex pos (m a) -> m (Vertex pos a)
$csequence :: forall pos (m :: * -> *) a.
Monad m =>
Vertex pos (m a) -> m (Vertex pos a)
mapM :: (a -> m b) -> Vertex pos a -> m (Vertex pos b)
$cmapM :: forall pos (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Vertex pos a -> m (Vertex pos b)
sequenceA :: Vertex pos (f a) -> f (Vertex pos a)
$csequenceA :: forall pos (f :: * -> *) a.
Applicative f =>
Vertex pos (f a) -> f (Vertex pos a)
traverse :: (a -> f b) -> Vertex pos a -> f (Vertex pos b)
$ctraverse :: forall pos (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Vertex pos a -> f (Vertex pos b)
$cp2Traversable :: forall pos. Foldable (Vertex pos)
$cp1Traversable :: forall pos. Functor (Vertex pos)
Traversable)

{-# INLINEABLE vertexAttrs #-}
vertexAttrs :: (pos -> a -> b) -> [Vertex pos a] -> [Vertex pos b]
vertexAttrs :: (pos -> a -> b) -> [Vertex pos a] -> [Vertex pos b]
vertexAttrs pos -> a -> b
inject [Vertex pos a]
vertices = do
  v :: Vertex pos a
v@Vertex{pos
a
vAttrs :: a
vPosition :: pos
$sel:vAttrs:Vertex :: forall pos attrs. Vertex pos attrs -> attrs
$sel:vPosition:Vertex :: forall pos attrs. Vertex pos attrs -> pos
..} <- [Vertex pos a]
vertices
  Vertex pos b -> [Vertex pos b]
forall (f :: * -> *) a. Applicative f => a -> f a
pure Vertex pos a
v
    { $sel:vAttrs:Vertex :: b
vAttrs = pos -> a -> b
inject pos
vPosition a
vAttrs
    }

{-# INLINEABLE vertexAttrsPos #-}
vertexAttrsPos :: (pos -> a) -> [pos] -> [Vertex pos a]
vertexAttrsPos :: (pos -> a) -> [pos] -> [Vertex pos a]
vertexAttrsPos pos -> a
inject [pos]
positions = do
  pos
pos <- [pos]
positions
  pure Vertex :: forall pos attrs. pos -> attrs -> Vertex pos attrs
Vertex
    { $sel:vPosition:Vertex :: pos
vPosition = pos
pos
    , $sel:vAttrs:Vertex :: a
vAttrs    = pos -> a
inject pos
pos
    }

class HasVertexBuffers a where
  type VertexBuffersOf a
  getVertexBuffers :: a -> [Vk.Buffer]
  getInstanceCount :: a -> Word32

instance HasVertexBuffers () where
  type VertexBuffersOf () = ()

  {-# INLINE getVertexBuffers #-}
  getVertexBuffers :: () -> [Buffer]
getVertexBuffers () = []

  {-# INLINE getInstanceCount #-}
  getInstanceCount :: () -> Word32
getInstanceCount () = Word32
1

instance HasVertexBuffers (Buffer.Allocated store a) where
  type VertexBuffersOf (Buffer.Allocated store a) = a

  {-# INLINE getVertexBuffers #-}
  getVertexBuffers :: Allocated store a -> [Buffer]
getVertexBuffers Buffer.Allocated{Buffer
$sel:aBuffer:Allocated :: forall (s :: Store) a. Allocated s a -> Buffer
aBuffer :: Buffer
aBuffer} = [Buffer
aBuffer]

  {-# INLINE getInstanceCount #-}
  getInstanceCount :: Allocated store a -> Word32
getInstanceCount = Allocated store a -> Word32
forall (store :: Store) a. Allocated store a -> Word32
Buffer.aUsed

data IndexRange = IndexRange
  { IndexRange -> Word32
irFirstIndex :: Word32
  , IndexRange -> Word32
irIndexCount :: Word32
  }
  deriving (IndexRange -> IndexRange -> Bool
(IndexRange -> IndexRange -> Bool)
-> (IndexRange -> IndexRange -> Bool) -> Eq IndexRange
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IndexRange -> IndexRange -> Bool
$c/= :: IndexRange -> IndexRange -> Bool
== :: IndexRange -> IndexRange -> Bool
$c== :: IndexRange -> IndexRange -> Bool
Eq, Eq IndexRange
Eq IndexRange
-> (IndexRange -> IndexRange -> Ordering)
-> (IndexRange -> IndexRange -> Bool)
-> (IndexRange -> IndexRange -> Bool)
-> (IndexRange -> IndexRange -> Bool)
-> (IndexRange -> IndexRange -> Bool)
-> (IndexRange -> IndexRange -> IndexRange)
-> (IndexRange -> IndexRange -> IndexRange)
-> Ord IndexRange
IndexRange -> IndexRange -> Bool
IndexRange -> IndexRange -> Ordering
IndexRange -> IndexRange -> IndexRange
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: IndexRange -> IndexRange -> IndexRange
$cmin :: IndexRange -> IndexRange -> IndexRange
max :: IndexRange -> IndexRange -> IndexRange
$cmax :: IndexRange -> IndexRange -> IndexRange
>= :: IndexRange -> IndexRange -> Bool
$c>= :: IndexRange -> IndexRange -> Bool
> :: IndexRange -> IndexRange -> Bool
$c> :: IndexRange -> IndexRange -> Bool
<= :: IndexRange -> IndexRange -> Bool
$c<= :: IndexRange -> IndexRange -> Bool
< :: IndexRange -> IndexRange -> Bool
$c< :: IndexRange -> IndexRange -> Bool
compare :: IndexRange -> IndexRange -> Ordering
$ccompare :: IndexRange -> IndexRange -> Ordering
$cp1Ord :: Eq IndexRange
Ord, Int -> IndexRange -> ShowS
[IndexRange] -> ShowS
IndexRange -> String
(Int -> IndexRange -> ShowS)
-> (IndexRange -> String)
-> ([IndexRange] -> ShowS)
-> Show IndexRange
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [IndexRange] -> ShowS
$cshowList :: [IndexRange] -> ShowS
show :: IndexRange -> String
$cshow :: IndexRange -> String
showsPrec :: Int -> IndexRange -> ShowS
$cshowsPrec :: Int -> IndexRange -> ShowS
Show, (forall x. IndexRange -> Rep IndexRange x)
-> (forall x. Rep IndexRange x -> IndexRange) -> Generic IndexRange
forall x. Rep IndexRange x -> IndexRange
forall x. IndexRange -> Rep IndexRange x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep IndexRange x -> IndexRange
$cfrom :: forall x. IndexRange -> Rep IndexRange x
Generic)

instance CBOR.Serialise IndexRange

instance Storable IndexRange where
  alignment :: IndexRange -> Int
alignment ~IndexRange
_ = Int
4

  sizeOf :: IndexRange -> Int
sizeOf ~IndexRange
_ = Int
8

  peek :: Ptr IndexRange -> IO IndexRange
peek Ptr IndexRange
ptr = do
    Word32
irFirstIndex <- Ptr IndexRange -> Int -> IO Word32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr IndexRange
ptr Int
0
    Word32
irIndexCount <- Ptr IndexRange -> Int -> IO Word32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr IndexRange
ptr Int
4
    pure IndexRange :: Word32 -> Word32 -> IndexRange
IndexRange{Word32
irIndexCount :: Word32
irFirstIndex :: Word32
$sel:irIndexCount:IndexRange :: Word32
$sel:irFirstIndex:IndexRange :: Word32
..}

  poke :: Ptr IndexRange -> IndexRange -> IO ()
poke Ptr IndexRange
ptr IndexRange{Word32
irIndexCount :: Word32
irFirstIndex :: Word32
$sel:irIndexCount:IndexRange :: IndexRange -> Word32
$sel:irFirstIndex:IndexRange :: IndexRange -> Word32
..} = do
    Ptr IndexRange -> Int -> Word32 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr IndexRange
ptr Int
0 Word32
irFirstIndex
    Ptr IndexRange -> Int -> Word32 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr IndexRange
ptr Int
4 Word32
irIndexCount

createStagedL
  :: (HasVulkan context, Storable pos, Storable attrs, MonadUnliftIO io)
  => context
  -> Queues Vk.CommandPool
  -> [Vertex pos attrs]
  -> Maybe [Word32]
  -> io (Indexed 'Buffer.Staged pos attrs)
createStagedL :: context
-> Queues CommandPool
-> [Vertex pos attrs]
-> Maybe [Word32]
-> io (Indexed 'Staged pos attrs)
createStagedL context
context Queues CommandPool
pool [Vertex pos attrs]
vertices Maybe [Word32]
mindices = context
-> Queues CommandPool
-> Vector pos
-> Vector attrs
-> Vector Word32
-> io (Indexed 'Staged pos attrs)
forall context pos attrs (io :: * -> *).
(HasVulkan context, Storable pos, Storable attrs,
 MonadUnliftIO io) =>
context
-> Queues CommandPool
-> Vector pos
-> Vector attrs
-> Vector Word32
-> io (Indexed 'Staged pos attrs)
createStaged context
context Queues CommandPool
pool Vector pos
pv Vector attrs
av Vector Word32
iv
  where
    pv :: Vector pos
pv = [pos] -> Vector pos
forall a. Storable a => [a] -> Vector a
Storable.fromList [pos]
ps
    av :: Vector attrs
av = [attrs] -> Vector attrs
forall a. Storable a => [a] -> Vector a
Storable.fromList [attrs]
as

    iv :: Vector Word32
iv = case Maybe [Word32]
mindices of
      Just [Word32]
is ->
        [Word32] -> Vector Word32
forall a. Storable a => [a] -> Vector a
Storable.fromList [Word32]
is
      Maybe [Word32]
Nothing ->
        -- TODO: add vertex deduplication
        Int -> (Int -> Word32) -> Vector Word32
forall a. Storable a => Int -> (Int -> a) -> Vector a
Storable.generate (Vector pos -> Int
forall a. Storable a => Vector a -> Int
Storable.length Vector pos
pv) Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral

    ([pos]
ps, [attrs]
as) = [(pos, attrs)] -> ([pos], [attrs])
forall a b. [(a, b)] -> ([a], [b])
List.unzip do
      Vertex{pos
attrs
vAttrs :: attrs
vPosition :: pos
$sel:vAttrs:Vertex :: forall pos attrs. Vertex pos attrs -> attrs
$sel:vPosition:Vertex :: forall pos attrs. Vertex pos attrs -> pos
..} <- [Vertex pos attrs]
vertices
      (pos, attrs) -> [(pos, attrs)]
forall (f :: * -> *) a. Applicative f => a -> f a
pure (pos
vPosition, attrs
vAttrs)

createStaged
  :: (HasVulkan context, Storable pos, Storable attrs, MonadUnliftIO io)
  => context
  -> Queues Vk.CommandPool
  -> Storable.Vector pos
  -> Storable.Vector attrs
  -> Storable.Vector Word32
  -> io (Indexed 'Buffer.Staged pos attrs)
createStaged :: context
-> Queues CommandPool
-> Vector pos
-> Vector attrs
-> Vector Word32
-> io (Indexed 'Staged pos attrs)
createStaged context
context Queues CommandPool
pool Vector pos
pv Vector attrs
av Vector Word32
iv = do
  Allocated 'Staged pos
positions <- context
-> Queues CommandPool
-> BufferUsageFlagBits
-> Int
-> Vector pos
-> io (Allocated 'Staged pos)
forall a context (io :: * -> *).
(Storable a, HasVulkan context, MonadUnliftIO io) =>
context
-> Queues CommandPool
-> BufferUsageFlagBits
-> Int
-> Vector a
-> io (Allocated 'Staged a)
Buffer.createStaged context
context Queues CommandPool
pool BufferUsageFlagBits
Vk.BUFFER_USAGE_VERTEX_BUFFER_BIT Int
0 Vector pos
pv
  Allocated 'Staged attrs
attrs     <- context
-> Queues CommandPool
-> BufferUsageFlagBits
-> Int
-> Vector attrs
-> io (Allocated 'Staged attrs)
forall a context (io :: * -> *).
(Storable a, HasVulkan context, MonadUnliftIO io) =>
context
-> Queues CommandPool
-> BufferUsageFlagBits
-> Int
-> Vector a
-> io (Allocated 'Staged a)
Buffer.createStaged context
context Queues CommandPool
pool BufferUsageFlagBits
Vk.BUFFER_USAGE_VERTEX_BUFFER_BIT Int
0 Vector attrs
av
  Allocated 'Staged Word32
indices   <- context
-> Queues CommandPool
-> BufferUsageFlagBits
-> Int
-> Vector Word32
-> io (Allocated 'Staged Word32)
forall a context (io :: * -> *).
(Storable a, HasVulkan context, MonadUnliftIO io) =>
context
-> Queues CommandPool
-> BufferUsageFlagBits
-> Int
-> Vector a
-> io (Allocated 'Staged a)
Buffer.createStaged context
context Queues CommandPool
pool BufferUsageFlagBits
Vk.BUFFER_USAGE_INDEX_BUFFER_BIT  Int
0 Vector Word32
iv
  pure Indexed :: forall (storage :: Store) pos attrs.
Allocated storage pos
-> Allocated storage attrs
-> Allocated storage Word32
-> Indexed storage pos attrs
Indexed
    { $sel:iPositions:Indexed :: Allocated 'Staged pos
iPositions = Allocated 'Staged pos
positions
    , $sel:iAttrs:Indexed :: Allocated 'Staged attrs
iAttrs     = Allocated 'Staged attrs
attrs
    , $sel:iIndices:Indexed :: Allocated 'Staged Word32
iIndices   = Allocated 'Staged Word32
indices
    }

createCoherentEmpty
  :: (HasVulkan context, Storable pos, Storable attrs, MonadUnliftIO io)
  => context
  -> Int
  -> io (Indexed 'Buffer.Coherent pos attrs)
createCoherentEmpty :: context -> Int -> io (Indexed 'Coherent pos attrs)
createCoherentEmpty context
ctx Int
initialSize = Allocated 'Coherent pos
-> Allocated 'Coherent attrs
-> Allocated 'Coherent Word32
-> Indexed 'Coherent pos attrs
forall (storage :: Store) pos attrs.
Allocated storage pos
-> Allocated storage attrs
-> Allocated storage Word32
-> Indexed storage pos attrs
Indexed
  (Allocated 'Coherent pos
 -> Allocated 'Coherent attrs
 -> Allocated 'Coherent Word32
 -> Indexed 'Coherent pos attrs)
-> io (Allocated 'Coherent pos)
-> io
     (Allocated 'Coherent attrs
      -> Allocated 'Coherent Word32 -> Indexed 'Coherent pos attrs)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> context
-> BufferUsageFlagBits
-> Int
-> Vector pos
-> io (Allocated 'Coherent pos)
forall a context (io :: * -> *).
(Storable a, HasVulkan context, MonadUnliftIO io) =>
context
-> BufferUsageFlagBits
-> Int
-> Vector a
-> io (Allocated 'Coherent a)
Buffer.createCoherent context
ctx BufferUsageFlagBits
Vk.BUFFER_USAGE_VERTEX_BUFFER_BIT Int
initialSize Vector pos
forall a. Monoid a => a
mempty
  io
  (Allocated 'Coherent attrs
   -> Allocated 'Coherent Word32 -> Indexed 'Coherent pos attrs)
-> io (Allocated 'Coherent attrs)
-> io (Allocated 'Coherent Word32 -> Indexed 'Coherent pos attrs)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> context
-> BufferUsageFlagBits
-> Int
-> Vector attrs
-> io (Allocated 'Coherent attrs)
forall a context (io :: * -> *).
(Storable a, HasVulkan context, MonadUnliftIO io) =>
context
-> BufferUsageFlagBits
-> Int
-> Vector a
-> io (Allocated 'Coherent a)
Buffer.createCoherent context
ctx BufferUsageFlagBits
Vk.BUFFER_USAGE_VERTEX_BUFFER_BIT Int
initialSize Vector attrs
forall a. Monoid a => a
mempty
  io (Allocated 'Coherent Word32 -> Indexed 'Coherent pos attrs)
-> io (Allocated 'Coherent Word32)
-> io (Indexed 'Coherent pos attrs)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> context
-> BufferUsageFlagBits
-> Int
-> Vector Word32
-> io (Allocated 'Coherent Word32)
forall a context (io :: * -> *).
(Storable a, HasVulkan context, MonadUnliftIO io) =>
context
-> BufferUsageFlagBits
-> Int
-> Vector a
-> io (Allocated 'Coherent a)
Buffer.createCoherent context
ctx BufferUsageFlagBits
Vk.BUFFER_USAGE_INDEX_BUFFER_BIT  Int
initialSize Vector Word32
forall a. Monoid a => a
mempty

destroyIndexed
  :: (HasVulkan context, MonadUnliftIO io)
  => context
  -> Indexed storage pos attrs
  -> io ()
destroyIndexed :: context -> Indexed storage pos attrs -> io ()
destroyIndexed context
ctx Indexed{Allocated storage pos
Allocated storage attrs
Allocated storage Word32
iIndices :: Allocated storage Word32
iAttrs :: Allocated storage attrs
iPositions :: Allocated storage pos
$sel:iIndices:Indexed :: forall (storage :: Store) pos attrs.
Indexed storage pos attrs -> Allocated storage Word32
$sel:iAttrs:Indexed :: forall (storage :: Store) pos attrs.
Indexed storage pos attrs -> Allocated storage attrs
$sel:iPositions:Indexed :: forall (storage :: Store) pos attrs.
Indexed storage pos attrs -> Allocated storage pos
..} = do
  context -> [Allocated storage pos] -> io ()
forall (io :: * -> *) context (t :: * -> *) (s :: Store) a.
(MonadUnliftIO io, HasVulkan context, Foldable t) =>
context -> t (Allocated s a) -> io ()
Buffer.destroyAll context
ctx [Allocated storage pos
iPositions]
  context -> [Allocated storage attrs] -> io ()
forall (io :: * -> *) context (t :: * -> *) (s :: Store) a.
(MonadUnliftIO io, HasVulkan context, Foldable t) =>
context -> t (Allocated s a) -> io ()
Buffer.destroyAll context
ctx [Allocated storage attrs
iAttrs]
  context -> [Allocated storage Word32] -> io ()
forall (io :: * -> *) context (t :: * -> *) (s :: Store) a.
(MonadUnliftIO io, HasVulkan context, Foldable t) =>
context -> t (Allocated s a) -> io ()
Buffer.destroyAll context
ctx [Allocated storage Word32
iIndices]

updateCoherent
  :: (HasVulkan context, Storable pos, Storable attrs, MonadUnliftIO io)
  => context
  -> [Vertex pos attrs]
  -> Indexed 'Buffer.Coherent pos attrs
  -> io (Indexed 'Buffer.Coherent pos attrs)
updateCoherent :: context
-> [Vertex pos attrs]
-> Indexed 'Coherent pos attrs
-> io (Indexed 'Coherent pos attrs)
updateCoherent context
ctx [Vertex pos attrs]
vertices Indexed 'Coherent pos attrs
old = do
  Indexed{Allocated 'Coherent pos
Allocated 'Coherent attrs
Allocated 'Coherent Word32
iIndices :: Allocated 'Coherent Word32
iAttrs :: Allocated 'Coherent attrs
iPositions :: Allocated 'Coherent pos
$sel:iIndices:Indexed :: forall (storage :: Store) pos attrs.
Indexed storage pos attrs -> Allocated storage Word32
$sel:iAttrs:Indexed :: forall (storage :: Store) pos attrs.
Indexed storage pos attrs -> Allocated storage attrs
$sel:iPositions:Indexed :: forall (storage :: Store) pos attrs.
Indexed storage pos attrs -> Allocated storage pos
..} <- io (Indexed 'Coherent pos attrs)
pick
  Allocated 'Coherent pos
-> Allocated 'Coherent attrs
-> Allocated 'Coherent Word32
-> Indexed 'Coherent pos attrs
forall (storage :: Store) pos attrs.
Allocated storage pos
-> Allocated storage attrs
-> Allocated storage Word32
-> Indexed storage pos attrs
Indexed
    (Allocated 'Coherent pos
 -> Allocated 'Coherent attrs
 -> Allocated 'Coherent Word32
 -> Indexed 'Coherent pos attrs)
-> io (Allocated 'Coherent pos)
-> io
     (Allocated 'Coherent attrs
      -> Allocated 'Coherent Word32 -> Indexed 'Coherent pos attrs)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Vector pos
-> Allocated 'Coherent pos -> io (Allocated 'Coherent pos)
forall a (io :: * -> *).
(Storable a, MonadUnliftIO io) =>
Vector a -> Allocated 'Coherent a -> io (Allocated 'Coherent a)
Buffer.updateCoherent Vector pos
pv Allocated 'Coherent pos
iPositions
    io
  (Allocated 'Coherent attrs
   -> Allocated 'Coherent Word32 -> Indexed 'Coherent pos attrs)
-> io (Allocated 'Coherent attrs)
-> io (Allocated 'Coherent Word32 -> Indexed 'Coherent pos attrs)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Vector attrs
-> Allocated 'Coherent attrs -> io (Allocated 'Coherent attrs)
forall a (io :: * -> *).
(Storable a, MonadUnliftIO io) =>
Vector a -> Allocated 'Coherent a -> io (Allocated 'Coherent a)
Buffer.updateCoherent Vector attrs
av Allocated 'Coherent attrs
iAttrs
    io (Allocated 'Coherent Word32 -> Indexed 'Coherent pos attrs)
-> io (Allocated 'Coherent Word32)
-> io (Indexed 'Coherent pos attrs)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Vector Word32
-> Allocated 'Coherent Word32 -> io (Allocated 'Coherent Word32)
forall a (io :: * -> *).
(Storable a, MonadUnliftIO io) =>
Vector a -> Allocated 'Coherent a -> io (Allocated 'Coherent a)
Buffer.updateCoherent Vector Word32
iv Allocated 'Coherent Word32
iIndices
  where
    pick :: io (Indexed 'Coherent pos attrs)
pick =
      if Int
oldSize Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
newSize then
        Indexed 'Coherent pos attrs -> io (Indexed 'Coherent pos attrs)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Indexed 'Coherent pos attrs
old
      else do
        context -> Indexed 'Coherent pos attrs -> io ()
forall context (io :: * -> *) (storage :: Store) pos attrs.
(HasVulkan context, MonadUnliftIO io) =>
context -> Indexed storage pos attrs -> io ()
destroyIndexed context
ctx Indexed 'Coherent pos attrs
old
        context -> Int -> io (Indexed 'Coherent pos attrs)
forall context pos attrs (io :: * -> *).
(HasVulkan context, Storable pos, Storable attrs,
 MonadUnliftIO io) =>
context -> Int -> io (Indexed 'Coherent pos attrs)
createCoherentEmpty context
ctx (Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
newSize (Int -> Int) -> Int -> Int
forall a b. (a -> b) -> a -> b
$ Int
oldSize Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
2)

    oldSize :: Int
oldSize = Allocated 'Coherent Word32 -> Int
forall (s :: Store) a. Allocated s a -> Int
Buffer.aCapacity (Allocated 'Coherent Word32 -> Int)
-> Allocated 'Coherent Word32 -> Int
forall a b. (a -> b) -> a -> b
$ Indexed 'Coherent pos attrs -> Allocated 'Coherent Word32
forall (storage :: Store) pos attrs.
Indexed storage pos attrs -> Allocated storage Word32
iIndices Indexed 'Coherent pos attrs
old
    newSize :: Int
newSize = Vector pos -> Int
forall a. Storable a => Vector a -> Int
Storable.length Vector pos
pv

    pv :: Vector pos
pv = [pos] -> Vector pos
forall a. Storable a => [a] -> Vector a
Storable.fromList [pos]
ps
    av :: Vector attrs
av = [attrs] -> Vector attrs
forall a. Storable a => [a] -> Vector a
Storable.fromList [attrs]
as

    iv :: Vector Word32
iv = Int -> (Int -> Word32) -> Vector Word32
forall a. Storable a => Int -> (Int -> a) -> Vector a
Storable.generate Int
newSize Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral

    ([pos]
ps, [attrs]
as) = [(pos, attrs)] -> ([pos], [attrs])
forall a b. [(a, b)] -> ([a], [b])
List.unzip do
      Vertex{pos
attrs
vAttrs :: attrs
vPosition :: pos
$sel:vAttrs:Vertex :: forall pos attrs. Vertex pos attrs -> attrs
$sel:vPosition:Vertex :: forall pos attrs. Vertex pos attrs -> pos
..} <- [Vertex pos attrs]
vertices
      (pos, attrs) -> [(pos, attrs)]
forall (f :: * -> *) a. Applicative f => a -> f a
pure (pos
vPosition, attrs
vAttrs)