2022-01-14 07:59:38 +00:00
|
|
|
{-# LANGUAGE OverloadedStrings #-}
|
|
|
|
{-# LANGUAGE DuplicateRecordFields #-}
|
|
|
|
{-# LANGUAGE DataKinds #-}
|
|
|
|
module Main where
|
|
|
|
|
|
|
|
import Control.Monad
|
|
|
|
import Control.Monad.Loops
|
|
|
|
import Control.Monad.IO.Class
|
|
|
|
import Control.Monad.Trans.Resource
|
2022-07-10 23:58:58 +00:00
|
|
|
import Data.Bits
|
2022-01-14 07:59:38 +00:00
|
|
|
import Data.Word
|
2022-07-10 17:31:44 +00:00
|
|
|
import qualified SDL hiding (V2)
|
2022-01-14 07:59:38 +00:00
|
|
|
import qualified Control.Concurrent.STM as STM
|
|
|
|
import qualified Vulkan as Vk
|
|
|
|
import qualified Vulkan.Zero as Vk
|
|
|
|
|
2022-07-10 23:58:58 +00:00
|
|
|
-- internal imports
|
|
|
|
|
|
|
|
import Init
|
2022-01-14 07:59:38 +00:00
|
|
|
|
|
|
|
main :: IO ()
|
|
|
|
main = runResourceT $ do
|
2022-07-10 17:31:44 +00:00
|
|
|
(window, inst, surface, swapchain, images) <- initEngine
|
2022-01-14 07:59:38 +00:00
|
|
|
|
|
|
|
SDL.showWindow window
|
|
|
|
|
|
|
|
-- create abort condition for upcoming lop
|
|
|
|
quit <- liftIO $ STM.newTMVarIO True
|
|
|
|
|
|
|
|
-- main loop
|
|
|
|
liftIO $ whileM_
|
|
|
|
(STM.atomically $ STM.readTMVar quit
|
|
|
|
)
|
|
|
|
( do
|
|
|
|
-- poll events
|
|
|
|
evs <- SDL.pollEvents
|
|
|
|
-- flip abort condition on window close
|
|
|
|
mapM_
|
|
|
|
(\e -> case SDL.eventPayload e of
|
|
|
|
SDL.WindowClosedEvent _ ->
|
|
|
|
void $ STM.atomically $ STM.swapTMVar quit False
|
|
|
|
_ -> return ()
|
|
|
|
)
|
|
|
|
evs
|
|
|
|
)
|
|
|
|
|
2022-07-10 23:58:58 +00:00
|
|
|
createBufferView
|
|
|
|
:: (MonadResource m)
|
|
|
|
=> Vk.Device
|
|
|
|
-> m (ReleaseKey, Vk.BufferView)
|
|
|
|
createBufferView logicalDevice = do
|
|
|
|
let bufferCreateInfo = Vk.zero
|
|
|
|
{ Vk.size = 1024
|
|
|
|
, Vk.usage =
|
|
|
|
Vk.BUFFER_USAGE_UNIFORM_BUFFER_BIT .|.
|
|
|
|
Vk.BUFFER_USAGE_UNIFORM_TEXEL_BUFFER_BIT
|
|
|
|
, Vk.sharingMode = Vk.SHARING_MODE_EXCLUSIVE
|
2022-01-14 07:59:38 +00:00
|
|
|
}
|
2022-07-10 23:58:58 +00:00
|
|
|
buffer <- snd <$> allocate
|
|
|
|
(Vk.createBuffer logicalDevice bufferCreateInfo Nothing)
|
|
|
|
(\buffer -> do
|
2022-07-12 14:31:40 +00:00
|
|
|
putStrLn "destroying buffer"
|
2022-07-10 23:58:58 +00:00
|
|
|
Vk.destroyBuffer logicalDevice buffer Nothing
|
2022-07-10 18:08:12 +00:00
|
|
|
)
|
2022-01-18 05:25:58 +00:00
|
|
|
|
2022-07-10 23:58:58 +00:00
|
|
|
let bufferViewCreateInfo = Vk.zero
|
|
|
|
{ Vk.buffer = buffer
|
|
|
|
, Vk.format = Vk.FORMAT_R32G32B32_SFLOAT
|
|
|
|
, Vk.offset = 0
|
|
|
|
, Vk.range = Vk.WHOLE_SIZE
|
2022-01-18 05:25:58 +00:00
|
|
|
}
|
2022-07-10 17:31:44 +00:00
|
|
|
|
2022-07-10 23:58:58 +00:00
|
|
|
allocate
|
|
|
|
(Vk.createBufferView logicalDevice bufferViewCreateInfo Nothing)
|
|
|
|
(\bufferView -> do
|
2022-07-12 14:31:40 +00:00
|
|
|
putStrLn "destroying bufferView"
|
2022-07-10 23:58:58 +00:00
|
|
|
Vk.destroyBufferView logicalDevice bufferView Nothing
|
2022-07-10 17:31:44 +00:00
|
|
|
)
|
|
|
|
|
2022-07-10 23:58:58 +00:00
|
|
|
allocateMemory
|
2022-07-10 17:31:44 +00:00
|
|
|
:: (MonadResource m)
|
2022-07-10 23:58:58 +00:00
|
|
|
=> Vk.Device
|
|
|
|
-> Vk.Buffer
|
|
|
|
-> m (ReleaseKey, Vk.DeviceMemory)
|
|
|
|
allocateMemory logicalDevice buffer = do
|
|
|
|
memoryRequirements <- Vk.getBufferMemoryRequirements logicalDevice buffer
|
|
|
|
|
|
|
|
let memoryAllocateInfo = Vk.zero
|
|
|
|
{ Vk.allocationSize = (Vk.size :: Vk.MemoryRequirements -> Word64) memoryRequirements
|
|
|
|
, Vk.memoryTypeIndex = error ("createBuffer: TODO: populate memoryTypeIndex!" :: String)
|
2022-07-10 17:31:44 +00:00
|
|
|
}
|
|
|
|
|
2022-07-10 23:58:58 +00:00
|
|
|
allocate
|
|
|
|
(Vk.allocateMemory logicalDevice memoryAllocateInfo Nothing)
|
|
|
|
(\memory -> do
|
2022-07-12 14:31:40 +00:00
|
|
|
putStrLn "Freeing memory"
|
2022-07-10 23:58:58 +00:00
|
|
|
Vk.freeMemory logicalDevice memory Nothing
|
2022-07-10 18:08:12 +00:00
|
|
|
)
|