Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data GlobalHandles = GlobalHandles {
- ghOptions :: Options
- ghWindow :: Window
- ghSurface :: SurfaceKHR
- ghInstance :: Instance
- ghPhysicalDevice :: PhysicalDevice
- ghPhysicalDeviceInfo :: PhysicalDeviceInfo
- ghDevice :: Device
- ghAllocator :: Allocator
- ghQueues :: Queues (QueueFamilyIndex, Queue)
- ghScreenVar :: Var Extent2D
- ghStageSwitch :: StageSwitchVar
- askScreenVar :: StageRIO env (Var Extent2D)
- type StageStack = [StackStage]
- data NextStage
- data StackStage where
- StackStage :: forall rp p rr st. RenderPass rp => Stage rp p rr st -> StackStage
- StackStageContinue :: forall rp p rr st. RenderPass rp => ReleaseKey -> st -> Stage rp p rr st -> StackStage
- type StageSwitchVar = TMVar StageSwitch
- data StageSwitch
- type StageRIO st = RIO (App GlobalHandles st)
- type StageSetupRIO = RIO (App GlobalHandles (Maybe SwapchainResources))
- type StageFrameRIO rp p rr st = RIO (App GlobalHandles st, Frame rp p rr)
- data Stage rp p rr st = forall a.Stage {
- sTitle :: Text
- sAllocateRP :: SwapchainResources -> ResourceT (StageRIO st) rp
- sAllocateP :: SwapchainResources -> rp -> ResourceT (StageRIO st) p
- sInitialRS :: StageRIO (Maybe SwapchainResources) (ReleaseKey, st)
- sInitialRR :: Queues CommandPool -> rp -> p -> ResourceT (StageRIO st) rr
- sBeforeLoop :: StageRIO st a
- sUpdateBuffers :: st -> rr -> StageFrameRIO rp p rr st ()
- sRecordCommands :: CommandBuffer -> rr -> ("image index" ::: Word32) -> StageFrameRIO rp p rr st ()
- sAfterLoop :: a -> StageRIO st ()
- data Frame renderpass pipelines resources = Frame {
- fIndex :: Word64
- fWindow :: Window
- fSurface :: SurfaceKHR
- fSwapchainResources :: SwapchainResources
- fRenderpass :: renderpass
- fPipelines :: pipelines
- fRenderFinishedHostSemaphore :: Semaphore
- fStageResources :: (RefCounted, InternalState)
- fGPUWork :: IORef [GPUWork]
- fResources :: (ReleaseKey, InternalState)
- fRecycledResources :: RecycledResources resources
- type GPUWork = ("host semaphore" ::: Semaphore, "frame index" ::: Word64)
- data RecycledResources a = RecycledResources {
- rrImageAvailableSemaphore :: Semaphore
- rrRenderFinishedSemaphore :: Semaphore
- rrQueues :: Queues CommandPool
- rrData :: a
App globals
data GlobalHandles Source #
A bunch of global, unchanging state we cart around
GlobalHandles | |
|
Instances
HasVulkan GlobalHandles Source # | |
Defined in Engine.Types getInstance :: GlobalHandles -> Instance Source # getQueues :: GlobalHandles -> Queues (QueueFamilyIndex, Queue) Source # getPhysicalDevice :: GlobalHandles -> PhysicalDevice Source # getPhysicalDeviceInfo :: GlobalHandles -> PhysicalDeviceInfo Source # getDevice :: GlobalHandles -> Device Source # getAllocator :: GlobalHandles -> Allocator Source # | |
HasStateRef st (App GlobalHandles st, Frame rp p rr) Source # | |
Defined in Engine.Types stateRefL :: Lens' (App GlobalHandles st, Frame rp p rr) (SomeRef st) |
askScreenVar :: StageRIO env (Var Extent2D) Source #
Stage stack
type StageStack = [StackStage] Source #
data StackStage where Source #
StackStage :: forall rp p rr st. RenderPass rp => Stage rp p rr st -> StackStage | |
StackStageContinue :: forall rp p rr st. RenderPass rp => ReleaseKey -> st -> Stage rp p rr st -> StackStage |
type StageSwitchVar = TMVar StageSwitch Source #
Stage on a stack
type StageRIO st = RIO (App GlobalHandles st) Source #
type StageSetupRIO = RIO (App GlobalHandles (Maybe SwapchainResources)) Source #
type StageFrameRIO rp p rr st = RIO (App GlobalHandles st, Frame rp p rr) Source #
data Stage rp p rr st Source #
forall a. Stage | |
|
Frame loop inside a stage
data Frame renderpass pipelines resources Source #
All the information required to render a single frame
Frame | |
|
Instances
HasDescSet tag rr => HasDescSet tag (env, Frame rp p rr) Source # | |
Defined in Engine.Vulkan.DescSets getDescSet :: (env, Frame rp p rr) -> Tagged tag DescriptorSet Source # | |
HasStateRef st (App GlobalHandles st, Frame rp p rr) Source # | |
Defined in Engine.Types stateRefL :: Lens' (App GlobalHandles st, Frame rp p rr) (SomeRef st) | |
HasDescSet tag rr => HasDescSet tag (Frame rp p rr) Source # | |
Defined in Engine.Vulkan.DescSets getDescSet :: Frame rp p rr -> Tagged tag DescriptorSet Source # | |
MonadResource (RIO (env, Frame rp p rr)) Source # | |
Defined in Engine.Types liftResourceT :: ResourceT IO a -> RIO (env, Frame rp p rr) a | |
HasLogFunc env => HasLogFunc (env, Frame rp p rr) Source # | |
Defined in Engine.Types |
data RecycledResources a Source #
These are resources which are reused by a later frame when the current frame is retired
RecycledResources | |
|
Instances
HasDescSet tag rr => HasDescSet tag (RecycledResources rr) Source # | |
Defined in Engine.Vulkan.DescSets getDescSet :: RecycledResources rr -> Tagged tag DescriptorSet Source # |