diff --git a/src/CommandBuffer.hs b/src/CommandBuffer.hs
index 1a9a66d..868a3b5 100644
--- a/src/CommandBuffer.hs
+++ b/src/CommandBuffer.hs
@@ -182,7 +182,8 @@ createFrames
 
 recordCommandBuffer
   :: (MonadResource m, MonadReader ReadState m, MonadIO m)
-  => Vk.CommandBuffer
+  => VMA.Allocator
+  -> Vk.CommandBuffer
   -> Vk.RenderPass
   -> Vk.Framebuffer
   -> V2 CInt
@@ -190,6 +191,7 @@ recordCommandBuffer
   -> FrameData
   -> m ()
 recordCommandBuffer
+  allocator
   commandBuffer
   renderPass
   frameBuffer
@@ -236,7 +238,7 @@ recordCommandBuffer
         let draws = compactDraws meshMap materialMap renderObjects
 
         let drawCommands = V.map
-              (\(i, RenderObject mesh matrix material) ->
+              (\(i, RenderObject mesh _ _) ->
                 Vk.DrawIndirectCommand
                   { vertexCount   = fromIntegral (V.length $ meshVertices $ meshMap M.! mesh)
                   , firstVertex   = 0
@@ -249,6 +251,24 @@ recordCommandBuffer
                 renderObjects
                 )
 
+        (memRelease, memPtr) <- VMA.withMappedMemory
+          allocator
+          (bufferAllocation $ frameIndirectBuffer frame)
+          allocate
+
+        V.mapM_
+          (\(idx, command) -> liftIO $
+            poke
+              (castPtr memPtr `plusPtr` (idx * sizeOf command))
+              command
+          )
+          (V.zip
+            (V.fromList [0 ..])
+            drawCommands
+           )
+
+        release memRelease
+
         V.mapM_
           (\(IndirectBatch mesh material first count) -> do
 
diff --git a/src/Draw.hs b/src/Draw.hs
index a9e7118..9239ee2 100644
--- a/src/Draw.hs
+++ b/src/Draw.hs
@@ -1,6 +1,7 @@
 {-# LANGUAGE OverloadedStrings #-}
 {-# LANGUAGE DuplicateRecordFields #-}
 {-# LANGUAGE FlexibleContexts #-}
+{-# LANGUAGE OverloadedRecordDot #-}
 module Draw where
 
 import qualified Control.Concurrent.STM as STM
@@ -80,6 +81,7 @@ drawFrame engineData frameNumber = do
     cameraData
 
   recordCommandBuffer
+    (engineData.engineAllocator)
     (frameMainCommandBuffer frame)
     (engineRenderPass engineData)
     (engineFramebuffers engineData V.! fromIntegral index)