-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Core parts of Keid engine. -- -- Core parts of Keid engine. @package keid-core @version 0.1.8.0 module Engine.Camera.Event.Type data Event Zoom :: Float -> Event Pan :: Vec3 -> Event PanHorizontal :: Float -> Event PanVertical :: Float -> Event TurnAzimuth :: Float -> Event TurnInclination :: Float -> Event instance GHC.Show.Show Engine.Camera.Event.Type.Event module Engine.DataRecycler data DataRecycler a DataRecycler :: DumpResource a -> WaitResource a -> DataRecycler a -- | Filled with resources which aren't destroyed after finishing a frame, -- but instead are used by another frame which executes after that one is -- retired, (taken from ghRecycleOut) -- -- Make sure not to pass any resources which were created with a -- frame-only scope however! [$sel:drDump:DataRecycler] :: DataRecycler a -> DumpResource a -- | The resources of prior frames waiting to be taken [$sel:drWait:DataRecycler] :: DataRecycler a -> WaitResource a type DumpResource a = a -> IO () type WaitResource a = IO (Either (IO a) a) new :: MonadIO m => m (DataRecycler a) module Engine.Setup.Window -- | Reprisents a GLFW window value. See the Window Guide data Window allocate :: (MonadUnliftIO m, MonadReader env m, HasLogFunc env, MonadResource m) => Bool -> Maybe (Int, Int) -> Natural -> SizePicker -> Text -> m ([InstanceRequirement], Window) createWindow :: (MonadIO m, MonadReader env m, HasLogFunc env) => Bool -> Maybe (Int, Int) -> Natural -> SizePicker -> Text -> m ([InstanceRequirement], Window) destroyWindow :: (MonadIO m, MonadReader env m, HasLogFunc env) => Window -> m () type SizePicker = NonEmpty (Monitor, VideoMode) -> (Monitor, VideoMode) pickLargest :: SizePicker -- | VkSurfaceKHR - Opaque handle to a surface object -- --

Description

-- -- The VK_KHR_surface extension declares the SurfaceKHR -- object, and provides a function for destroying SurfaceKHR -- objects. Separate platform-specific extensions each provide a function -- for creating a SurfaceKHR object for the respective platform. -- From the application’s perspective this is an opaque handle, just like -- the handles of other Vulkan objects. -- --

See Also

-- -- VK_KHR_surface, PhysicalDeviceSurfaceInfo2KHR, -- SwapchainCreateInfoKHR, createAndroidSurfaceKHR, -- createDirectFBSurfaceEXT, createDisplayPlaneSurfaceKHR, -- createHeadlessSurfaceEXT, createIOSSurfaceMVK, -- createImagePipeSurfaceFUCHSIA, createMacOSSurfaceMVK, -- createMetalSurfaceEXT, createScreenSurfaceQNX, -- createStreamDescriptorSurfaceGGP, createViSurfaceNN, -- createWaylandSurfaceKHR, createWin32SurfaceKHR, -- createXcbSurfaceKHR, createXlibSurfaceKHR, -- destroySurfaceKHR, getDeviceGroupSurfacePresentModesKHR, -- getPhysicalDevicePresentRectanglesKHR, -- getPhysicalDeviceSurfaceCapabilities2EXT, -- getPhysicalDeviceSurfaceCapabilitiesKHR, -- getPhysicalDeviceSurfaceFormatsKHR, -- getPhysicalDeviceSurfacePresentModesKHR, -- getPhysicalDeviceSurfaceSupportKHR data SurfaceKHR allocateSurface :: MonadResource m => Window -> Instance -> m (ReleaseKey, SurfaceKHR) createSurface :: MonadIO m => Window -> Instance -> m SurfaceKHR getExtent2D :: Window -> IO Extent2D data GLFWError -- | An enum for one of the GLFW error codes. data Error instance GHC.Show.Show Engine.Setup.Window.GLFWError instance GHC.Classes.Ord Engine.Setup.Window.GLFWError instance GHC.Classes.Eq Engine.Setup.Window.GLFWError instance GHC.Exception.Type.Exception Engine.Setup.Window.GLFWError module Engine.Types.RefCounted -- | A RefCounted will perform the specified action when the count -- reaches 0 data RefCounted RefCounted :: IORef Int -> IO () -> RefCounted [$sel:rcCount:RefCounted] :: RefCounted -> IORef Int [$sel:rcAction:RefCounted] :: RefCounted -> IO () -- | Create a counter with a value of 1 newRefCounted :: MonadIO m => IO () -> m RefCounted -- | Decrement the value, the action will be run promptly and in this -- thread if the counter reached 0. releaseRefCounted :: MonadIO m => RefCounted -> m () -- | Increment the counter by 1 takeRefCounted :: MonadIO m => RefCounted -> m () -- | Hold a reference for the duration of the MonadResource action resourceTRefCount :: MonadResource f => RefCounted -> f () wrapped :: MonadResource m => m (ReleaseKey, a) -> m (RefCounted, a) module Engine.Vulkan.Format class HasVkFormat a getVkFormat :: HasVkFormat a => [Format] getVkFormat :: (HasVkFormat a, GVkFormat (Rep a)) => [Format] genericVkFormat :: forall a. GVkFormat (Rep a) => [Format] formatSize :: Integral a => Format -> a instance Engine.Vulkan.Format.HasVkFormat () instance Engine.Vulkan.Format.HasVkFormat GHC.Types.Float instance Engine.Vulkan.Format.HasVkFormat Geomancy.Vec2.Vec2 instance Engine.Vulkan.Format.HasVkFormat Geomancy.Vec3.Vec3 instance Engine.Vulkan.Format.HasVkFormat Geomancy.Vec3.Packed instance Engine.Vulkan.Format.HasVkFormat Geomancy.Vec4.Vec4 instance Engine.Vulkan.Format.HasVkFormat Geomancy.Quaternion.Quaternion instance Engine.Vulkan.Format.HasVkFormat Geomancy.Mat4.Mat4 instance Engine.Vulkan.Format.HasVkFormat Geomancy.Transform.Transform instance Engine.Vulkan.Format.HasVkFormat GHC.Int.Int32 instance Engine.Vulkan.Format.HasVkFormat Geomancy.IVec2.IVec2 instance Engine.Vulkan.Format.HasVkFormat Geomancy.IVec3.IVec3 instance Engine.Vulkan.Format.HasVkFormat Geomancy.IVec3.Packed instance Engine.Vulkan.Format.HasVkFormat Geomancy.IVec4.IVec4 instance Engine.Vulkan.Format.HasVkFormat GHC.Word.Word32 instance Engine.Vulkan.Format.HasVkFormat Geomancy.UVec2.UVec2 instance Engine.Vulkan.Format.HasVkFormat Geomancy.UVec3.UVec3 instance Engine.Vulkan.Format.HasVkFormat Geomancy.UVec3.Packed instance Engine.Vulkan.Format.HasVkFormat Geomancy.UVec4.UVec4 instance Engine.Vulkan.Format.HasVkFormat v => Engine.Vulkan.Format.HasVkFormat (Geomancy.Point.Point v) instance Engine.Vulkan.Format.HasVkFormat a => Engine.Vulkan.Format.GVkFormat (GHC.Generics.K1 r a) instance Engine.Vulkan.Format.GVkFormat f => Engine.Vulkan.Format.GVkFormat (GHC.Generics.M1 c cb f) instance (Engine.Vulkan.Format.GVkFormat l, Engine.Vulkan.Format.GVkFormat r) => Engine.Vulkan.Format.GVkFormat (l GHC.Generics.:*: r) module Engine.Vulkan.Pipeline.Stages class (Applicative t, Traversable t) => StageInfo t stageNames :: (StageInfo t, IsString label) => t label stageFlagBits :: StageInfo t => t ShaderStageFlagBits withLabels :: (StageInfo t, IsString label) => t a -> t (label, a) module Engine.SpirV.Reflect invoke :: MonadIO m => FilePath -> m Module data Reflect stages Reflect :: BindMap BlockBinding -> StageInterface stages -> Text -> InterfaceBinds -> Reflect stages [$sel:bindMap:Reflect] :: Reflect stages -> BindMap BlockBinding [$sel:interfaces:Reflect] :: Reflect stages -> StageInterface stages [$sel:inputStage:Reflect] :: Reflect stages -> Text [$sel:inputs:Reflect] :: Reflect stages -> InterfaceBinds -- |
--   layout(set=X, binding=Y) ...
--   
type BindMap a = IntMap (IntMap a) type StageInterface stages = stages (Maybe (InterfaceBinds, InterfaceBinds)) -- | @layout(location=N) type InterfaceBinds = IntMap InterfaceBinding -- |
--   uniform Foo { ... } foo;
--   
type BlockBinding = (Text, DescriptorType, Maybe (Tree ([Maybe Text], BlockSignature))) data BlockSignature BlockSignature :: Word32 -> Word32 -> TypeFlags -> Maybe Scalar -> BlockSignature [$sel:offset:BlockSignature] :: BlockSignature -> Word32 [$sel:size:BlockSignature] :: BlockSignature -> Word32 [$sel:flags:BlockSignature] :: BlockSignature -> TypeFlags [$sel:scalar:BlockSignature] :: BlockSignature -> Maybe Scalar stagesBindMap :: (MonadIO m, MonadReader env m, HasLogFunc env, StageInfo stages) => stages (Maybe Module) -> m (BindMap BlockBinding) moduleBindMap :: Module -> BindMap BlockBinding blockTree :: [Maybe Text] -> BlockVariable -> Tree ([Maybe Text], BlockSignature) bindMapUnionWith :: (a -> a -> Bool) -> BindMap a -> BindMap a -> Either (Int, Int, a, a) (BindMap a) type InterfaceBinding = (Maybe Text, [Text], InterfaceSignature) data InterfaceSignature InterfaceSignature :: Format -> TypeFlags -> Maybe Matrix -> InterfaceSignature [$sel:format:InterfaceSignature] :: InterfaceSignature -> Format [$sel:flags:InterfaceSignature] :: InterfaceSignature -> TypeFlags [$sel:matrix:InterfaceSignature] :: InterfaceSignature -> Maybe Matrix stagesInterfaceMap :: Traversable stages => stages (Maybe Module) -> StageInterface stages moduleInterfaceBinds :: Module -> (InterfaceBinds, InterfaceBinds) interfaceBinds :: StorageClass -> Vector InterfaceVariable -> InterfaceBinds type IncompatibleInterfaces label = (label, label, Int, Maybe (InterfaceSignature, InterfaceSignature)) type CompatibleInterfaces label = (label, label, IntMap ([Text], Matching (Maybe Text))) type Matching a = Either (a, a) a interfaceCompatible :: (StageInfo stages, IsString label) => StageInterface stages -> Either (IncompatibleInterfaces label) [CompatibleInterfaces label] inputStageInterface :: (StageInfo stages, IsString label) => StageInterface stages -> Maybe (label, InterfaceBinds) instance GHC.Show.Show Engine.SpirV.Reflect.BlockSignature instance GHC.Classes.Ord Engine.SpirV.Reflect.BlockSignature instance GHC.Classes.Eq Engine.SpirV.Reflect.BlockSignature instance GHC.Show.Show Engine.SpirV.Reflect.InterfaceSignature instance GHC.Classes.Ord Engine.SpirV.Reflect.InterfaceSignature instance GHC.Classes.Eq Engine.SpirV.Reflect.InterfaceSignature instance GHC.Classes.Eq (Engine.SpirV.Reflect.StageInterface stages) => GHC.Classes.Eq (Engine.SpirV.Reflect.Reflect stages) instance GHC.Show.Show (Engine.SpirV.Reflect.StageInterface stages) => GHC.Show.Show (Engine.SpirV.Reflect.Reflect stages) module Engine.Vulkan.Types type MonadVulkan env m = (MonadUnliftIO m, MonadReader env m, HasVulkan env) -- | A class for Monads which can provide some Vulkan handles class HasVulkan a getInstance :: HasVulkan a => a -> Instance getQueues :: HasVulkan a => a -> Queues (QueueFamilyIndex, Queue) getPhysicalDevice :: HasVulkan a => a -> PhysicalDevice getPhysicalDeviceInfo :: HasVulkan a => a -> PhysicalDeviceInfo getDevice :: HasVulkan a => a -> Device getAllocator :: HasVulkan a => a -> Allocator getPipelineCache :: ctx -> PipelineCache class HasSwapchain a getSurfaceExtent :: HasSwapchain a => a -> Extent2D getSurfaceFormat :: HasSwapchain a => a -> Format getDepthFormat :: HasSwapchain a => a -> Format getMultisample :: HasSwapchain a => a -> SampleCountFlagBits getAnisotropy :: HasSwapchain a => a -> "max sampler anisotropy" ::: Float getSwapchainViews :: HasSwapchain a => a -> Vector ImageView getMinImageCount :: HasSwapchain a => a -> Word32 getImageCount :: HasSwapchain a => a -> Word32 class HasRenderPass a getFramebuffers :: HasRenderPass a => a -> Vector Framebuffer getRenderPass :: HasRenderPass a => a -> RenderPass getClearValues :: HasRenderPass a => a -> Vector ClearValue getRenderArea :: HasRenderPass a => a -> Rect2D class RenderPass a updateRenderpass :: (RenderPass a, HasLogFunc env, HasSwapchain swapchain, HasVulkan env, MonadResource (RIO env)) => swapchain -> a -> RIO env a refcountRenderpass :: (RenderPass a, MonadResource (RIO env)) => a -> RIO env () data PhysicalDeviceInfo PhysicalDeviceInfo :: Word64 -> Vector (DeviceQueueCreateInfo '[]) -> Text -> PhysicalDeviceProperties -> (Device -> IO (Queues (QueueFamilyIndex, Queue))) -> PhysicalDeviceInfo [$sel:pdiTotalMemory:PhysicalDeviceInfo] :: PhysicalDeviceInfo -> Word64 [$sel:pdiQueueCreateInfos:PhysicalDeviceInfo] :: PhysicalDeviceInfo -> Vector (DeviceQueueCreateInfo '[]) [$sel:pdiName:PhysicalDeviceInfo] :: PhysicalDeviceInfo -> Text [$sel:pdiProperties:PhysicalDeviceInfo] :: PhysicalDeviceInfo -> PhysicalDeviceProperties [$sel:pdiGetQueues:PhysicalDeviceInfo] :: PhysicalDeviceInfo -> Device -> IO (Queues (QueueFamilyIndex, Queue)) -- | The shape of all the queues we use for our program, parameterized over -- the queue type so we can use it with assignQueues. data Queues q Queues :: q -> q -> q -> Queues q [$sel:qGraphics:Queues] :: Queues q -> q [$sel:qTransfer:Queues] :: Queues q -> q [$sel:qCompute:Queues] :: Queues q -> q type DsLayouts = Vector DescriptorSetLayout type DsLayoutBindings = [(DescriptorSetLayoutBinding, DescriptorBindingFlags)] newtype Bound (dsl :: [Type]) vertices instances m a Bound :: m a -> Bound (dsl :: [Type]) vertices instances m a instance Data.Traversable.Traversable Engine.Vulkan.Types.Queues instance Data.Foldable.Foldable Engine.Vulkan.Types.Queues instance GHC.Base.Functor Engine.Vulkan.Types.Queues instance GHC.Show.Show q => GHC.Show.Show (Engine.Vulkan.Types.Queues q) instance Control.Monad.State.Class.MonadState s m => Control.Monad.State.Class.MonadState s (Engine.Vulkan.Types.Bound dsl vertices instances m) instance Control.Monad.Reader.Class.MonadReader r m => Control.Monad.Reader.Class.MonadReader r (Engine.Vulkan.Types.Bound dsl vertices instances m) instance Control.Monad.IO.Unlift.MonadUnliftIO m => Control.Monad.IO.Unlift.MonadUnliftIO (Engine.Vulkan.Types.Bound dsl vertices instances m) instance Control.Monad.IO.Class.MonadIO m => Control.Monad.IO.Class.MonadIO (Engine.Vulkan.Types.Bound dsl vertices instances m) instance GHC.Base.Monad m => GHC.Base.Monad (Engine.Vulkan.Types.Bound dsl vertices instances m) instance GHC.Base.Applicative m => GHC.Base.Applicative (Engine.Vulkan.Types.Bound dsl vertices instances m) instance GHC.Base.Functor m => GHC.Base.Functor (Engine.Vulkan.Types.Bound dsl vertices instances m) instance Data.Traversable.Traversable m => Data.Traversable.Traversable (Engine.Vulkan.Types.Bound dsl vertices instances m) instance Data.Foldable.Foldable m => Data.Foldable.Foldable (Engine.Vulkan.Types.Bound dsl vertices instances m) instance Engine.Vulkan.Types.HasVulkan env => Engine.Vulkan.Types.HasVulkan (RIO.App.App env st) instance Engine.Vulkan.Types.HasVulkan env => Engine.Vulkan.Types.HasVulkan (env, a) module Engine.Vulkan.Pipeline data Pipeline (dsl :: [Type]) vertices instances Pipeline :: Pipeline -> Tagged dsl PipelineLayout -> Tagged dsl DsLayouts -> Pipeline (dsl :: [Type]) vertices instances [$sel:pipeline:Pipeline] :: Pipeline (dsl :: [Type]) vertices instances -> Pipeline [$sel:pLayout:Pipeline] :: Pipeline (dsl :: [Type]) vertices instances -> Tagged dsl PipelineLayout [$sel:pDescLayouts:Pipeline] :: Pipeline (dsl :: [Type]) vertices instances -> Tagged dsl DsLayouts allocateWith :: (MonadVulkan env m, MonadResource m) => m (Pipeline dsl vertices instances) -> m (ReleaseKey, Pipeline dsl vertices instances) type family Specialization pipeline -- | Physical device tools module Engine.Setup.Device allocatePhysical :: (MonadUnliftIO m, MonadThrow m, MonadReader env m, HasLogFunc env, MonadResource m) => Instance -> Maybe SurfaceKHR -> (PhysicalDeviceInfo -> Word64) -> m (PhysicalDeviceInfo, PhysicalDevice) physicalDeviceInfo :: (MonadIO m, MonadReader env m, HasLogFunc env) => Maybe SurfaceKHR -> PhysicalDevice -> m (Maybe PhysicalDeviceInfo) -- | Requirements for a Queue which has graphics support and can -- present to the specified surface. -- -- Priorities are ranged 0.0 to 1.0 with higher number means higher -- priority. -- https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#devsandqueues-priority queueRequirements :: MonadIO m => PhysicalDevice -> Maybe SurfaceKHR -> Queues (QueueSpec m) deviceHasSwapchain :: MonadIO m => PhysicalDevice -> m Bool deviceHasTimelineSemaphores :: MonadIO m => PhysicalDevice -> m Bool allocateLogical :: (MonadUnliftIO m, MonadReader env m, HasLogFunc env, MonadResource m) => PhysicalDeviceInfo -> PhysicalDevice -> m Device noSuchThing :: MonadThrow m => String -> m a module Engine.Worker data Versioned a Versioned :: Vector Word64 -> a -> Versioned a [$sel:vVersion:Versioned] :: Versioned a -> Vector Word64 [$sel:vData:Versioned] :: Versioned a -> a type Var a = TVar (Versioned a) newVar :: MonadUnliftIO m => a -> m (Var a) readVar :: MonadUnliftIO m => Var a -> m a stateVar :: HasInput var => var -> StateVar (GetInput var) stateVarMap :: HasInput var => (GetInput var -> a) -> (a -> GetInput var -> GetInput var) -> var -> StateVar a class HasInput a where { type GetInput a; } getInput :: HasInput a => a -> Var (GetInput a) pushInput :: (MonadIO m, HasInput var) => var -> (GetInput var -> GetInput var) -> m () pushInputSTM :: HasInput var => var -> (GetInput var -> GetInput var) -> STM () updateInput :: (MonadIO m, HasInput var) => var -> (GetInput var -> Maybe (GetInput var)) -> m () updateInputSTM :: HasInput var => var -> (GetInput var -> Maybe (GetInput var)) -> STM () getInputData :: (HasInput worker, MonadIO m) => worker -> m (GetInput worker) getInputDataSTM :: HasInput worker => worker -> STM (GetInput worker) class HasConfig a where { type GetConfig a; } getConfig :: HasConfig a => a -> TVar (GetConfig a) modifyConfig :: (MonadIO m, HasConfig var) => var -> (GetConfig var -> GetConfig var) -> m () modifyConfigSTM :: HasConfig var => var -> (GetConfig var -> GetConfig var) -> STM () class HasOutput a where { type GetOutput a; } getOutput :: HasOutput a => a -> Var (GetOutput a) pushOutput :: (MonadIO m, HasOutput var) => var -> (GetOutput var -> GetOutput var) -> m () pushOutputSTM :: HasOutput var => var -> (GetOutput var -> GetOutput var) -> STM () updateOutput :: (MonadIO m, HasOutput var) => var -> (GetOutput var -> Maybe (GetOutput var)) -> m () updateOutputSTM :: HasOutput var => var -> (GetOutput var -> Maybe (GetOutput var)) -> STM () getOutputData :: (HasOutput worker, MonadIO m) => worker -> m (GetOutput worker) getOutputDataSTM :: HasOutput worker => worker -> STM (GetOutput worker) -- | Updatable cell for composite input or costly output. type Cell input output = (Var input, Merge output) spawnCell :: (MonadUnliftIO m, MonadResource m) => (input -> output) -> input -> m (Cell input output) -- | Timer-driven stateful producer. data Timed config output Timed :: ThreadId -> ReleaseKey -> TVar Bool -> TVar config -> Var output -> Timed config output [$sel:tWorker:Timed] :: Timed config output -> ThreadId [$sel:tKey:Timed] :: Timed config output -> ReleaseKey [$sel:tActive:Timed] :: Timed config output -> TVar Bool [$sel:tConfig:Timed] :: Timed config output -> TVar config [$sel:tOutput:Timed] :: Timed config output -> Var output spawnTimed :: (MonadUnliftIO m, MonadResource m) => Bool -> Either Int (config -> Int) -> (config -> m (output, state)) -> (state -> config -> m (Maybe output, state)) -> config -> m (Timed config output) spawnTimed_ :: (MonadUnliftIO m, MonadResource m) => Bool -> Int -> output -> m output -> m (Timed () output) -- | Supply-driven step cell. data Merge o Merge :: ThreadId -> ReleaseKey -> TVar (Versioned o) -> Merge o [$sel:mWorker:Merge] :: Merge o -> ThreadId [$sel:mKey:Merge] :: Merge o -> ReleaseKey [$sel:mOutput:Merge] :: Merge o -> TVar (Versioned o) spawnMerge1 :: (MonadUnliftIO m, MonadResource m, HasOutput i) => (GetOutput i -> o) -> i -> m (Merge o) spawnMerge2 :: (MonadUnliftIO m, MonadResource m, HasOutput i1, HasOutput i2) => (GetOutput i1 -> GetOutput i2 -> o) -> i1 -> i2 -> m (Merge o) spawnMerge3 :: (MonadUnliftIO m, MonadResource m, HasOutput i1, HasOutput i2, HasOutput i3) => (GetOutput i1 -> GetOutput i2 -> GetOutput i3 -> o) -> i1 -> i2 -> i3 -> m (Merge o) spawnMerge4 :: (MonadUnliftIO m, MonadResource m, HasOutput i1, HasOutput i2, HasOutput i3, HasOutput i4) => (GetOutput i1 -> GetOutput i2 -> GetOutput i3 -> GetOutput i4 -> o) -> i1 -> i2 -> i3 -> i4 -> m (Merge o) -- | Spawn a merge over a homogeneous traversable collection of processes. -- -- A merging function will receive a collection of outputs to summarize. spawnMergeT :: (Traversable t, HasOutput input, MonadUnliftIO m, MonadResource m) => (t (GetOutput input) -> output) -> t input -> m (Merge output) type ObserverIO a = IORef (Versioned a) newObserverIO :: MonadIO m => a -> m (ObserverIO a) observeIO :: (MonadUnliftIO m, HasOutput output) => output -> ObserverIO a -> (a -> GetOutput output -> m a) -> m a observeIO_ :: (MonadUnliftIO m, HasOutput output) => output -> ObserverIO a -> (a -> GetOutput output -> m a) -> m () readObservedIO :: MonadUnliftIO m => IORef (Versioned a) -> m a data Source a newSource :: (MonadUnliftIO m, UnagiPrim a) => m (Source a) pubSource :: (MonadUnliftIO m, UnagiPrim a) => Source a -> a -> m () subSource :: MonadUnliftIO m => Source a -> m (OutChan a) instance Data.Traversable.Traversable Engine.Worker.Versioned instance Data.Foldable.Foldable Engine.Worker.Versioned instance GHC.Base.Functor Engine.Worker.Versioned instance GHC.Show.Show a => GHC.Show.Show (Engine.Worker.Versioned a) instance Engine.Worker.HasOutput (Engine.Worker.Merge o) instance Engine.Worker.HasConfig (Engine.Worker.Timed config output) instance Engine.Worker.HasOutput (Engine.Worker.Timed config output) instance Engine.Worker.HasOutput (Engine.Worker.Var a) instance Engine.Worker.HasOutput b => Engine.Worker.HasOutput (a, b) instance Engine.Worker.HasConfig (GHC.Conc.Sync.TVar a) instance Engine.Worker.HasInput (Engine.Worker.Var a) instance Engine.Worker.HasInput a => Engine.Worker.HasInput (a, b) instance GHC.Classes.Eq (Engine.Worker.Versioned a) instance GHC.Classes.Ord (Engine.Worker.Versioned a) module Engine.Vulkan.Swapchain data SwapchainResources SwapchainResources :: SwapchainInfo -> Vector ImageView -> Vector Image -> RefCounted -> Var Extent2D -> SwapchainResources [$sel:srInfo:SwapchainResources] :: SwapchainResources -> SwapchainInfo [$sel:srImageViews:SwapchainResources] :: SwapchainResources -> Vector ImageView [$sel:srImages:SwapchainResources] :: SwapchainResources -> Vector Image [$sel:srRelease:SwapchainResources] :: SwapchainResources -> RefCounted [$sel:srScreenVar:SwapchainResources] :: SwapchainResources -> Var Extent2D data SwapchainInfo SwapchainInfo :: SwapchainKHR -> ReleaseKey -> PresentModeKHR -> Word32 -> Format -> ColorSpaceKHR -> Format -> SampleCountFlagBits -> Float -> Extent2D -> SurfaceKHR -> SwapchainInfo [$sel:siSwapchain:SwapchainInfo] :: SwapchainInfo -> SwapchainKHR [$sel:siSwapchainReleaseKey:SwapchainInfo] :: SwapchainInfo -> ReleaseKey [$sel:siPresentMode:SwapchainInfo] :: SwapchainInfo -> PresentModeKHR [$sel:siMinImageCount:SwapchainInfo] :: SwapchainInfo -> Word32 [$sel:siSurfaceFormat:SwapchainInfo] :: SwapchainInfo -> Format [$sel:siSurfaceColorspace:SwapchainInfo] :: SwapchainInfo -> ColorSpaceKHR [$sel:siDepthFormat:SwapchainInfo] :: SwapchainInfo -> Format [$sel:siMultisample:SwapchainInfo] :: SwapchainInfo -> SampleCountFlagBits [$sel:siAnisotropy:SwapchainInfo] :: SwapchainInfo -> Float [$sel:siImageExtent:SwapchainInfo] :: SwapchainInfo -> Extent2D [$sel:siSurface:SwapchainInfo] :: SwapchainInfo -> SurfaceKHR -- | Allocate everything which depends on the swapchain allocSwapchainResources :: (MonadResource (RIO env), HasVulkan env, HasLogFunc env) => Maybe PresentModeKHR -> SampleCountFlagBits -> SwapchainKHR -> Extent2D -> SurfaceKHR -> Var Extent2D -> RIO env SwapchainResources recreateSwapchainResources :: (MonadResource (RIO env), HasVulkan env, HasLogFunc env) => Maybe PresentModeKHR -> SampleCountFlagBits -> Extent2D -> SwapchainResources -> RIO env SwapchainResources -- | Create a swapchain from a SurfaceKHR createSwapchain :: (MonadResource m, MonadVulkan env m, HasLogFunc env) => Maybe PresentModeKHR -> SampleCountFlagBits -> SwapchainKHR -> Extent2D -> SurfaceKHR -> m SwapchainInfo -- | Catch an ERROR_OUT_OF_DATE_KHR exception and return True if -- that happened threwSwapchainError :: MonadUnliftIO f => f () -> f Bool class HasSwapchain a getSurfaceExtent :: HasSwapchain a => a -> Extent2D getSurfaceFormat :: HasSwapchain a => a -> Format getDepthFormat :: HasSwapchain a => a -> Format getMultisample :: HasSwapchain a => a -> SampleCountFlagBits getAnisotropy :: HasSwapchain a => a -> "max sampler anisotropy" ::: Float getSwapchainViews :: HasSwapchain a => a -> Vector ImageView getMinImageCount :: HasSwapchain a => a -> Word32 getImageCount :: HasSwapchain a => a -> Word32 setDynamic :: MonadIO io => CommandBuffer -> ("viewport" ::: Rect2D) -> ("scissor" ::: Rect2D) -> io () setDynamicFullscreen :: (HasSwapchain swapchain, MonadIO io) => CommandBuffer -> swapchain -> io () instance Engine.Vulkan.Types.HasSwapchain Engine.Vulkan.Swapchain.SwapchainResources module Engine.Types.Options -- | Command line arguments data Options Options :: Bool -> Maybe Int -> Maybe PresentModeKHR -> SampleCountFlagBits -> Bool -> Natural -> Maybe (Int, Int) -> Maybe Int -> Options [$sel:optionsVerbose:Options] :: Options -> Bool [$sel:optionsMaxFPS:Options] :: Options -> Maybe Int [$sel:optionsPresent:Options] :: Options -> Maybe PresentModeKHR [$sel:optionsMsaa:Options] :: Options -> SampleCountFlagBits [$sel:optionsFullscreen:Options] :: Options -> Bool [$sel:optionsDisplay:Options] :: Options -> Natural [$sel:optionsSize:Options] :: Options -> Maybe (Int, Int) [$sel:optionsRecyclerWait:Options] :: Options -> Maybe Int getOptions :: IO Options optionsP :: Parser Options instance GHC.Show.Show Engine.Types.Options.Options module Engine.Types -- | A bunch of global, unchanging state we cart around data GlobalHandles GlobalHandles :: Options -> Window -> SurfaceKHR -> Instance -> PhysicalDevice -> PhysicalDeviceInfo -> Device -> Allocator -> Queues (QueueFamilyIndex, Queue) -> Var Extent2D -> StageSwitchVar -> GlobalHandles [$sel:ghOptions:GlobalHandles] :: GlobalHandles -> Options [$sel:ghWindow:GlobalHandles] :: GlobalHandles -> Window [$sel:ghSurface:GlobalHandles] :: GlobalHandles -> SurfaceKHR [$sel:ghInstance:GlobalHandles] :: GlobalHandles -> Instance [$sel:ghPhysicalDevice:GlobalHandles] :: GlobalHandles -> PhysicalDevice [$sel:ghPhysicalDeviceInfo:GlobalHandles] :: GlobalHandles -> PhysicalDeviceInfo [$sel:ghDevice:GlobalHandles] :: GlobalHandles -> Device [$sel:ghAllocator:GlobalHandles] :: GlobalHandles -> Allocator [$sel:ghQueues:GlobalHandles] :: GlobalHandles -> Queues (QueueFamilyIndex, Queue) [$sel:ghScreenVar:GlobalHandles] :: GlobalHandles -> Var Extent2D [$sel:ghStageSwitch:GlobalHandles] :: GlobalHandles -> StageSwitchVar askScreenVar :: MonadReader (App GlobalHandles st) m => m (Var Extent2D) type StageStack = [StackStage] data NextStage Finish :: NextStage Replace :: StackStage -> NextStage PushRestart :: StackStage -> NextStage PushFreeze :: StackStage -> NextStage data StackStage [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 StageSwitchPending :: NextStage -> StageSwitch StageSwitchHandled :: 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 Stage :: Text -> (SwapchainResources -> ResourceT (StageRIO st) rp) -> (SwapchainResources -> rp -> ResourceT (StageRIO st) p) -> StageRIO (Maybe SwapchainResources) (ReleaseKey, st) -> (Queues CommandPool -> rp -> p -> ResourceT (StageRIO st) rr) -> StageRIO st a -> (st -> rr -> StageFrameRIO rp p rr st ()) -> (CommandBuffer -> rr -> ("image index" ::: Word32) -> StageFrameRIO rp p rr st ()) -> (a -> StageRIO st ()) -> Stage rp p rr st [$sel:sTitle:Stage] :: Stage rp p rr st -> Text [$sel:sAllocateRP:Stage] :: Stage rp p rr st -> SwapchainResources -> ResourceT (StageRIO st) rp [$sel:sAllocateP:Stage] :: Stage rp p rr st -> SwapchainResources -> rp -> ResourceT (StageRIO st) p [$sel:sInitialRS:Stage] :: Stage rp p rr st -> StageRIO (Maybe SwapchainResources) (ReleaseKey, st) [$sel:sInitialRR:Stage] :: Stage rp p rr st -> Queues CommandPool -> rp -> p -> ResourceT (StageRIO st) rr [$sel:sBeforeLoop:Stage] :: Stage rp p rr st -> StageRIO st a [$sel:sUpdateBuffers:Stage] :: Stage rp p rr st -> st -> rr -> StageFrameRIO rp p rr st () [$sel:sRecordCommands:Stage] :: Stage rp p rr st -> CommandBuffer -> rr -> ("image index" ::: Word32) -> StageFrameRIO rp p rr st () [$sel:sAfterLoop:Stage] :: Stage rp p rr st -> a -> StageRIO st () -- | All the information required to render a single frame data Frame renderpass pipelines resources Frame :: Word64 -> Window -> SurfaceKHR -> Maybe PresentModeKHR -> SampleCountFlagBits -> SwapchainResources -> renderpass -> pipelines -> Semaphore -> (RefCounted, InternalState) -> IORef [GPUWork] -> (ReleaseKey, InternalState) -> RecycledResources resources -> Frame renderpass pipelines resources -- | Which number frame is this [$sel:fIndex:Frame] :: Frame renderpass pipelines resources -> Word64 [$sel:fWindow:Frame] :: Frame renderpass pipelines resources -> Window [$sel:fSurface:Frame] :: Frame renderpass pipelines resources -> SurfaceKHR [$sel:fPresent:Frame] :: Frame renderpass pipelines resources -> Maybe PresentModeKHR [$sel:fMSAA:Frame] :: Frame renderpass pipelines resources -> SampleCountFlagBits [$sel:fSwapchainResources:Frame] :: Frame renderpass pipelines resources -> SwapchainResources [$sel:fRenderpass:Frame] :: Frame renderpass pipelines resources -> renderpass [$sel:fPipelines:Frame] :: Frame renderpass pipelines resources -> pipelines -- | A timeline semaphore which increments to fIndex when this frame is -- done, the host can wait on this semaphore. [$sel:fRenderFinishedHostSemaphore:Frame] :: Frame renderpass pipelines resources -> Semaphore -- | Swapchain-derived resources with a life time of this Frame's stage. [$sel:fStageResources:Frame] :: Frame renderpass pipelines resources -> (RefCounted, InternalState) -- | Timeline semaphores and corresponding wait values, updates as the -- frame progresses. [$sel:fGPUWork:Frame] :: Frame renderpass pipelines resources -> IORef [GPUWork] -- | The InternalState for tracking frame-local resources along -- with the key to release it in the global scope. This will be released -- when the frame is done with GPU work. [$sel:fResources:Frame] :: Frame renderpass pipelines resources -> (ReleaseKey, InternalState) -- | Resources which can be used for this frame and are then passed on to a -- later frame. [$sel:fRecycledResources:Frame] :: Frame renderpass pipelines resources -> RecycledResources resources type GPUWork = ("host semaphore" ::: Semaphore, "frame index" ::: Word64) -- | These are resources which are reused by a later frame when the current -- frame is retired data RecycledResources a RecycledResources :: Semaphore -> Semaphore -> Queues CommandPool -> a -> RecycledResources a -- | A binary semaphore passed to acquireNextImageKHR [$sel:rrImageAvailableSemaphore:RecycledResources] :: RecycledResources a -> Semaphore -- | A binary semaphore to synchronize rendering and presenting [$sel:rrRenderFinishedSemaphore:RecycledResources] :: RecycledResources a -> Semaphore -- | Pool for this frame's commands for each of the queue families. (might -- want more than one of these for multithreaded recording) [$sel:rrQueues:RecycledResources] :: RecycledResources a -> Queues CommandPool [$sel:rrData:RecycledResources] :: RecycledResources a -> a type family HKD f a instance Engine.Vulkan.Types.HasVulkan Engine.Types.GlobalHandles instance RIO.Prelude.RIO.HasStateRef st (RIO.App.App Engine.Types.GlobalHandles st, Engine.Types.Frame rp p rr) instance Engine.Vulkan.Types.HasSwapchain (Engine.Types.Frame renderpass pipelines resources) instance RIO.Prelude.Logger.HasLogFunc env => RIO.Prelude.Logger.HasLogFunc (env, Engine.Types.Frame rp p rr) instance Control.Monad.Trans.Resource.Internal.MonadResource (RIO.Prelude.RIO.RIO (env, Engine.Types.Frame rp p rr)) module Engine.Vulkan.DescSets class HasDescSet tag a getDescSet :: HasDescSet tag a => a -> Tagged tag DescriptorSet newtype Bound (dsl :: [Type]) vertices instances m a Bound :: m a -> Bound (dsl :: [Type]) vertices instances m a withBoundDescriptorSets0 :: MonadIO m => CommandBuffer -> PipelineBindPoint -> Tagged dsl PipelineLayout -> Tagged dsl (Vector DescriptorSet) -> Bound dsl Void Void m b -> m b type Compatible (smaller :: [Type]) (larger :: [Type]) = Compatible' smaller larger smaller larger type family Extend (xs :: [Type]) y :: [Type] extendDS :: Tagged (as :: [Type]) (Vector DescriptorSet) -> Tagged b DescriptorSet -> Tagged (Extend as b) (Vector DescriptorSet) -- | A Tagged s b value is a value b with an -- attached phantom type s. This can be used in place of the -- more traditional but less safe idiom of passing in an undefined value -- with the type, because unlike an (s -> b), a -- Tagged s b can't try to use the argument s as -- a real value. -- -- Moreover, you don't have to rely on the compiler to inline away the -- extra argument, because the newtype is "free" -- -- Tagged has kind k -> * -> * if the compiler -- supports PolyKinds, therefore there is an extra k -- showing in the instance haddocks that may cause confusion. newtype Tagged (s :: k) b Tagged :: b -> Tagged (s :: k) b [unTagged] :: Tagged (s :: k) b -> b instance Engine.Vulkan.DescSets.HasDescSet tag rr => Engine.Vulkan.DescSets.HasDescSet tag (Engine.Types.RecycledResources rr) instance Engine.Vulkan.DescSets.HasDescSet tag rr => Engine.Vulkan.DescSets.HasDescSet tag (Engine.Types.Frame rp p rr) instance Engine.Vulkan.DescSets.HasDescSet tag rr => Engine.Vulkan.DescSets.HasDescSet tag (env, Engine.Types.Frame rp p rr) module Engine.UI.Layout type BoxProcess = Merge Box data Box Box :: Vec2 -> Vec2 -> Box [$sel:boxPosition:Box] :: Box -> Vec2 [$sel:boxSize:Box] :: Box -> Vec2 trackScreen :: (MonadReader (App GlobalHandles st) m, MonadResource m, MonadUnliftIO m) => m BoxProcess padAbs :: (MonadResource m, MonadUnliftIO m, HasOutput parent, GetOutput parent ~ Box, HasOutput padding, GetOutput padding ~ Vec4) => parent -> padding -> m BoxProcess hSplitRel :: (MonadResource m, MonadUnliftIO m, HasOutput parent, GetOutput parent ~ Box, HasOutput proportion, GetOutput proportion ~ Float) => parent -> proportion -> m (BoxProcess, BoxProcess) vSplitRel :: (MonadUnliftIO m, MonadResource m, HasOutput parent, GetOutput parent ~ Box, HasOutput proportion, GetOutput proportion ~ Float) => parent -> proportion -> m (BoxProcess, BoxProcess) splitsRelStatic :: (MonadResource m, MonadUnliftIO m, HasOutput parent, GetOutput parent ~ Box, Traversable t) => ((Float, Float) -> Vec4) -> parent -> t Float -> m (t BoxProcess) sharePadsH :: (Float, Float) -> Vec4 sharePadsV :: (Float, Float) -> Vec4 boxPadAbs :: Box -> Vec4 -> Box sharePads :: Traversable t => Float -> t Float -> t (Float, Float) fitPlaceAbs :: (MonadResource m, MonadUnliftIO m, HasOutput parent, GetOutput parent ~ Box) => Alignment -> ("dimensions" ::: Vec2) -> parent -> m BoxProcess boxFitPlace :: Alignment -> ("dimensions" ::: Vec2) -> ("parent" ::: Box) -> Box boxFitScale :: ("dimensions" ::: Vec2) -> ("parent" ::: Box) -> ("leftovers" ::: Vec2, Box) boxRectAbs :: Box -> Rect2D boxTransformAbs :: Box -> Transform data Alignment Alignment :: Origin -> Origin -> Alignment -- | leftcenterright [$sel:alignX:Alignment] :: Alignment -> Origin -- | topmiddlebottom [$sel:alignY:Alignment] :: Alignment -> Origin pattern LeftTop :: Alignment pattern LeftMiddle :: Alignment pattern LeftBottom :: Alignment pattern CenterTop :: Alignment pattern Center :: Alignment pattern CenterBottom :: Alignment pattern RightTop :: Alignment pattern RightMiddle :: Alignment pattern RightBottom :: Alignment data Origin Begin :: Origin Middle :: Origin End :: Origin whenInBoxP :: (MonadIO m, HasOutput box, GetOutput box ~ Box) => ("screen" ::: Vec2) -> box -> (("local" ::: Vec2) -> m ()) -> m () pointInBox :: Vec2 -> Box -> Bool instance GHC.Show.Show Engine.UI.Layout.Box instance GHC.Classes.Ord Engine.UI.Layout.Box instance GHC.Classes.Eq Engine.UI.Layout.Box instance GHC.Enum.Bounded Engine.UI.Layout.Origin instance GHC.Enum.Enum Engine.UI.Layout.Origin instance GHC.Show.Show Engine.UI.Layout.Origin instance GHC.Classes.Ord Engine.UI.Layout.Origin instance GHC.Classes.Eq Engine.UI.Layout.Origin module Engine.UI.Layout.Linear hBoxShares :: Traversable t => t Float -> Box -> t Box hBoxSplitRel :: Float -> Box -> (Box, Box) vBoxShares :: Traversable t => t Float -> Box -> t Box vBoxSplitRel :: Float -> Box -> (Box, Box) placeBox :: Vec2 -> Vec2 -> Box -> Box place :: Num b => b -> b -> b -> (b, b) ranges :: (Traversable t, Num a) => t a -> (a, t (a, a)) midpoints :: (Functor f, Fractional a) => f (a, a) -> f a module Engine.StageSwitch type StageSwitchVar = TMVar StageSwitch newStageSwitchVar :: MonadIO m => m StageSwitchVar data StageSwitch StageSwitchPending :: NextStage -> StageSwitch StageSwitchHandled :: StageSwitch trySwitchStage :: NextStage -> StageRIO rs Bool trySwitchStageSTM :: StageSwitchVar -> NextStage -> STM Bool getNextStage :: StageRIO rs (Maybe NextStage) module Engine.Events.Sink newtype Sink event rs Sink :: (forall m. MonadSink rs m => event -> m ()) -> Sink event rs [$sel:signal:Sink] :: Sink event rs -> forall m. MonadSink rs m => event -> m () spawn :: MonadSink rs m => (event -> m ()) -> m (ReleaseKey, Sink event rs) -- | A collection of properties that are available while handling events. -- Has access to a stage RunState, but not Frame data. type MonadSink rs m = (MonadReader (App GlobalHandles rs) m, MonadState rs m, MonadResource m, MonadUnliftIO m) module Engine.Window.Scroll type Callback m = Double -> Double -> m () callback :: MonadSink rs m => Callback m -> m ReleaseKey mkCallback :: UnliftIO m -> Callback m -> ScrollCallback module Engine.Window.Key type Callback m = Int -> (ModifierKeys, KeyState, Key) -> m () callback :: MonadSink rs m => Callback m -> m ReleaseKey -- | Part of the Keyboard Input system. data Key Key'Unknown :: Key Key'Space :: Key Key'Apostrophe :: Key Key'Comma :: Key Key'Minus :: Key Key'Period :: Key Key'Slash :: Key Key'0 :: Key Key'1 :: Key Key'2 :: Key Key'3 :: Key Key'4 :: Key Key'5 :: Key Key'6 :: Key Key'7 :: Key Key'8 :: Key Key'9 :: Key Key'Semicolon :: Key Key'Equal :: Key Key'A :: Key Key'B :: Key Key'C :: Key Key'D :: Key Key'E :: Key Key'F :: Key Key'G :: Key Key'H :: Key Key'I :: Key Key'J :: Key Key'K :: Key Key'L :: Key Key'M :: Key Key'N :: Key Key'O :: Key Key'P :: Key Key'Q :: Key Key'R :: Key Key'S :: Key Key'T :: Key Key'U :: Key Key'V :: Key Key'W :: Key Key'X :: Key Key'Y :: Key Key'Z :: Key Key'LeftBracket :: Key Key'Backslash :: Key Key'RightBracket :: Key Key'GraveAccent :: Key Key'World1 :: Key Key'World2 :: Key Key'Escape :: Key Key'Enter :: Key Key'Tab :: Key Key'Backspace :: Key Key'Insert :: Key Key'Delete :: Key Key'Right :: Key Key'Left :: Key Key'Down :: Key Key'Up :: Key Key'PageUp :: Key Key'PageDown :: Key Key'Home :: Key Key'End :: Key Key'CapsLock :: Key Key'ScrollLock :: Key Key'NumLock :: Key Key'PrintScreen :: Key Key'Pause :: Key Key'F1 :: Key Key'F2 :: Key Key'F3 :: Key Key'F4 :: Key Key'F5 :: Key Key'F6 :: Key Key'F7 :: Key Key'F8 :: Key Key'F9 :: Key Key'F10 :: Key Key'F11 :: Key Key'F12 :: Key Key'F13 :: Key Key'F14 :: Key Key'F15 :: Key Key'F16 :: Key Key'F17 :: Key Key'F18 :: Key Key'F19 :: Key Key'F20 :: Key Key'F21 :: Key Key'F22 :: Key Key'F23 :: Key Key'F24 :: Key Key'F25 :: Key Key'Pad0 :: Key Key'Pad1 :: Key Key'Pad2 :: Key Key'Pad3 :: Key Key'Pad4 :: Key Key'Pad5 :: Key Key'Pad6 :: Key Key'Pad7 :: Key Key'Pad8 :: Key Key'Pad9 :: Key Key'PadDecimal :: Key Key'PadDivide :: Key Key'PadMultiply :: Key Key'PadSubtract :: Key Key'PadAdd :: Key Key'PadEnter :: Key Key'PadEqual :: Key Key'LeftShift :: Key Key'LeftControl :: Key Key'LeftAlt :: Key Key'LeftSuper :: Key Key'RightShift :: Key Key'RightControl :: Key Key'RightAlt :: Key Key'RightSuper :: Key Key'Menu :: Key -- | The state of an individual key when getKey is called. data KeyState KeyState'Pressed :: KeyState KeyState'Released :: KeyState KeyState'Repeating :: KeyState -- | Modifier keys that were pressed as part of another keypress event. data ModifierKeys ModifierKeys :: !Bool -> !Bool -> !Bool -> !Bool -> !Bool -> !Bool -> ModifierKeys [modifierKeysShift] :: ModifierKeys -> !Bool [modifierKeysControl] :: ModifierKeys -> !Bool [modifierKeysAlt] :: ModifierKeys -> !Bool [modifierKeysSuper] :: ModifierKeys -> !Bool [modifierKeysCapsLock] :: ModifierKeys -> !Bool [modifierKeysNumLock] :: ModifierKeys -> !Bool mkCallback :: UnliftIO m -> Callback m -> KeyCallback module Engine.Window.Drop type Callback m = [FilePath] -> m () callback :: MonadSink rs m => Callback m -> m ReleaseKey mkCallback :: UnliftIO m -> Callback m -> DropCallback module Engine.Window.CursorPos type Callback m = Double -> Double -> m () callback :: MonadSink rs m => Callback m -> m ReleaseKey -- | Part of the Mouse Input system. data MouseButton MouseButton'1 :: MouseButton MouseButton'2 :: MouseButton MouseButton'3 :: MouseButton MouseButton'4 :: MouseButton MouseButton'5 :: MouseButton MouseButton'6 :: MouseButton MouseButton'7 :: MouseButton MouseButton'8 :: MouseButton -- | If the mouse button is pressed or not when getMouseButton is -- called. data MouseButtonState MouseButtonState'Pressed :: MouseButtonState MouseButtonState'Released :: MouseButtonState -- | Modifier keys that were pressed as part of another keypress event. data ModifierKeys ModifierKeys :: !Bool -> !Bool -> !Bool -> !Bool -> !Bool -> !Bool -> ModifierKeys [modifierKeysShift] :: ModifierKeys -> !Bool [modifierKeysControl] :: ModifierKeys -> !Bool [modifierKeysAlt] :: ModifierKeys -> !Bool [modifierKeysSuper] :: ModifierKeys -> !Bool [modifierKeysCapsLock] :: ModifierKeys -> !Bool [modifierKeysNumLock] :: ModifierKeys -> !Bool mkCallback :: UnliftIO m -> Callback m -> CursorPosCallback module Engine.Events newtype Sink event rs Sink :: (forall m. MonadSink rs m => event -> m ()) -> Sink event rs [$sel:signal:Sink] :: Sink event rs -> forall m. MonadSink rs m => event -> m () spawn :: MonadSink st m => (event -> m ()) -> [Sink event st -> m ReleaseKey] -> m (ReleaseKey, Sink event st) registerMany :: MonadResource m => [m ReleaseKey] -> m ReleaseKey module Engine.Events.CursorPos callback :: (MonadSink rs m, HasInput cursor, GetInput cursor ~ Vec2) => cursor -> Sink e st -> m ReleaseKey handler :: (MonadResource m, HasInput cursor, GetInput cursor ~ Vec2) => cursor -> Sink e st -> Callback m type Process = Cell ("window" ::: Vec2) ("centered" ::: Vec2) spawn :: MonadSink rs m => m Process module Engine.Camera data ProjectionKind Perspective :: ProjectionKind Orthographic :: ProjectionKind data Projection (pk :: ProjectionKind) Projection :: Transform -> ~Transform -> Projection (pk :: ProjectionKind) [$sel:projectionTransform:Projection] :: Projection (pk :: ProjectionKind) -> Transform [$sel:projectionInverse:Projection] :: Projection (pk :: ProjectionKind) -> ~Transform type family ProjectionParams (pk :: ProjectionKind) data ProjectionInput (pk :: ProjectionKind) ProjectionInput :: ProjectionParams pk -> Float -> Float -> ProjectionInput (pk :: ProjectionKind) [$sel:projectionParams:ProjectionInput] :: ProjectionInput (pk :: ProjectionKind) -> ProjectionParams pk [$sel:projectionNear:ProjectionInput] :: ProjectionInput (pk :: ProjectionKind) -> Float [$sel:projectionFar:ProjectionInput] :: ProjectionInput (pk :: ProjectionKind) -> Float type ProjectionProcess pk = Cell (ProjectionInput pk) (Projection pk) spawnPerspective :: (MonadReader (App GlobalHandles st) m, MonadResource m, MonadUnliftIO m) => m (ProjectionProcess 'Perspective) mkTransformPerspective :: Extent2D -> ProjectionInput 'Perspective -> Transform spawnOrthoPixelsCentered :: (MonadReader (App GlobalHandles st) m, MonadResource m, MonadUnliftIO m) => m (ProjectionProcess 'Orthographic) mkTransformOrthoPixelsCentered :: Extent2D -> ProjectionInput 'Orthographic -> Transform spawnProjectionWith :: (MonadReader (App GlobalHandles st) m, MonadResource m, MonadUnliftIO m) => (Extent2D -> ProjectionInput pk -> Transform) -> ProjectionInput pk -> m (ProjectionProcess pk) spawnProjection :: (MonadReader (App GlobalHandles st) m, MonadResource m, MonadUnliftIO m) => (Extent2D -> ProjectionInput pk -> Transform) -> ProjectionParams pk -> m (ProjectionProcess pk) pattern PROJECTION_NEAR :: (Eq a, Num a, Fractional a) => a pattern PROJECTION_FAR :: (Eq a, Num a) => a data View View :: Transform -> Transform -> Vec3 -> Vec3 -> View [$sel:viewTransform:View] :: View -> Transform [$sel:viewTransformInv:View] :: View -> Transform [$sel:viewPosition:View] :: View -> Vec3 [$sel:viewDirection:View] :: View -> Vec3 type ViewProcess = Cell ViewOrbitalInput View -- | Camera orbiting its target data ViewOrbitalInput ViewOrbitalInput :: Float -> Float -> Float -> Float -> Vec3 -> Vec3 -> Vec3 -> ViewOrbitalInput [$sel:orbitAzimuth:ViewOrbitalInput] :: ViewOrbitalInput -> Float [$sel:orbitAscent:ViewOrbitalInput] :: ViewOrbitalInput -> Float [$sel:orbitDistance:ViewOrbitalInput] :: ViewOrbitalInput -> Float [$sel:orbitScale:ViewOrbitalInput] :: ViewOrbitalInput -> Float [$sel:orbitTarget:ViewOrbitalInput] :: ViewOrbitalInput -> Vec3 [$sel:orbitUp:ViewOrbitalInput] :: ViewOrbitalInput -> Vec3 [$sel:orbitRight:ViewOrbitalInput] :: ViewOrbitalInput -> Vec3 initialOrbitalInput :: ViewOrbitalInput mkViewOrbital :: Vec3 -> ViewOrbitalInput -> View mkViewOrbital_ :: ViewOrbitalInput -> View instance GHC.Generics.Generic Engine.Camera.ProjectionKind instance GHC.Enum.Bounded Engine.Camera.ProjectionKind instance GHC.Enum.Enum Engine.Camera.ProjectionKind instance GHC.Show.Show Engine.Camera.ProjectionKind instance GHC.Classes.Ord Engine.Camera.ProjectionKind instance GHC.Classes.Eq Engine.Camera.ProjectionKind instance GHC.Generics.Generic (Engine.Camera.Projection pk) instance GHC.Show.Show (Engine.Camera.Projection pk) instance GHC.Show.Show Engine.Camera.View instance GHC.Show.Show Engine.Camera.ViewOrbitalInput module Engine.Camera.Controls type ProjectionProcess pk = Cell (ProjectionInput pk) (Projection pk) type ViewProcess = Cell ViewOrbitalInput View spawnViewOrbital :: (MonadResource m, MonadUnliftIO m) => ViewOrbitalInput -> m ViewProcess data Controls a Controls :: a -> a -> a -> a -> Controls a [$sel:panHorizontal:Controls] :: Controls a -> a [$sel:panVertical:Controls] :: Controls a -> a [$sel:turnAzimuth:Controls] :: Controls a -> a [$sel:turnInclination:Controls] :: Controls a -> a type ControlsProcess = Controls (Timed Float ()) spawnControls :: (MonadResource m, MonadUnliftIO m) => ViewProcess -> m ControlsProcess panInstant :: MonadIO m => ViewProcess -> Vec3 -> m () instance Data.Traversable.Traversable Engine.Camera.Controls.Controls instance Data.Foldable.Foldable Engine.Camera.Controls.Controls instance GHC.Base.Functor Engine.Camera.Controls.Controls module Engine.Camera.Event.Handler handler :: MonadIO m => m ViewProcess -> m ControlsProcess -> Event -> m () module Engine.Setup setup :: (HasLogFunc env, MonadResource (RIO env)) => Options -> RIO env (GlobalHandles, Maybe SwapchainResources) vmaVulkanFunctions :: Device -> Instance -> VulkanFunctions setupHeadless :: (HasLogFunc env, MonadResource (RIO env)) => Options -> RIO env Headless data Headless Headless :: Instance -> PhysicalDeviceInfo -> PhysicalDevice -> Device -> Allocator -> Queues (QueueFamilyIndex, Queue) -> Headless [$sel:hInstance:Headless] :: Headless -> Instance [$sel:hPhysicalDeviceInfo:Headless] :: Headless -> PhysicalDeviceInfo [$sel:hPhysicalDevice:Headless] :: Headless -> PhysicalDevice [$sel:hDevice:Headless] :: Headless -> Device [$sel:hAllocator:Headless] :: Headless -> Allocator [$sel:hQueues:Headless] :: Headless -> Queues (QueueFamilyIndex, Queue) deviceProps :: InstanceRequirement debugUtils :: InstanceRequirement headlessReqs :: [InstanceRequirement] instance Engine.Vulkan.Types.HasVulkan Engine.Setup.Headless module Engine.Frame -- | All the information required to render a single frame data Frame renderpass pipelines resources Frame :: Word64 -> Window -> SurfaceKHR -> Maybe PresentModeKHR -> SampleCountFlagBits -> SwapchainResources -> renderpass -> pipelines -> Semaphore -> (RefCounted, InternalState) -> IORef [GPUWork] -> (ReleaseKey, InternalState) -> RecycledResources resources -> Frame renderpass pipelines resources -- | Which number frame is this [$sel:fIndex:Frame] :: Frame renderpass pipelines resources -> Word64 [$sel:fWindow:Frame] :: Frame renderpass pipelines resources -> Window [$sel:fSurface:Frame] :: Frame renderpass pipelines resources -> SurfaceKHR [$sel:fPresent:Frame] :: Frame renderpass pipelines resources -> Maybe PresentModeKHR [$sel:fMSAA:Frame] :: Frame renderpass pipelines resources -> SampleCountFlagBits [$sel:fSwapchainResources:Frame] :: Frame renderpass pipelines resources -> SwapchainResources [$sel:fRenderpass:Frame] :: Frame renderpass pipelines resources -> renderpass [$sel:fPipelines:Frame] :: Frame renderpass pipelines resources -> pipelines -- | A timeline semaphore which increments to fIndex when this frame is -- done, the host can wait on this semaphore. [$sel:fRenderFinishedHostSemaphore:Frame] :: Frame renderpass pipelines resources -> Semaphore -- | Swapchain-derived resources with a life time of this Frame's stage. [$sel:fStageResources:Frame] :: Frame renderpass pipelines resources -> (RefCounted, InternalState) -- | Timeline semaphores and corresponding wait values, updates as the -- frame progresses. [$sel:fGPUWork:Frame] :: Frame renderpass pipelines resources -> IORef [GPUWork] -- | The InternalState for tracking frame-local resources along -- with the key to release it in the global scope. This will be released -- when the frame is done with GPU work. [$sel:fResources:Frame] :: Frame renderpass pipelines resources -> (ReleaseKey, InternalState) -- | Resources which can be used for this frame and are then passed on to a -- later frame. [$sel:fRecycledResources:Frame] :: Frame renderpass pipelines resources -> RecycledResources resources initial :: Maybe SwapchainResources -> DumpResource (RecycledResources rr) -> Stage rp p rr st -> StageRIO st (Frame rp p rr) run :: (HasLogFunc env, HasVulkan env, MonadResource (RIO env)) => (RecycledResources rr -> IO ()) -> Maybe Int -> RIO (env, Frame rp p rr) a -> Frame rp p rr -> RIO env a -- | Derive next frame advance :: (HasLogFunc env, HasVulkan env, MonadResource (RIO env), RenderPass rp) => WaitResource (RecycledResources rr) -> Frame rp p rr -> Bool -> RIO env (Frame rp p rr) -- | queueSubmit and add wait for the timeline Semaphore -- before retiring the frame. queueSubmit :: MonadVulkan env m => Queue -> Vector (SomeStruct SubmitInfo) -> IORef [GPUWork] -> Semaphore -> Word64 -> m () -- | These are resources which are reused by a later frame when the current -- frame is retired data RecycledResources a RecycledResources :: Semaphore -> Semaphore -> Queues CommandPool -> a -> RecycledResources a -- | A binary semaphore passed to acquireNextImageKHR [$sel:rrImageAvailableSemaphore:RecycledResources] :: RecycledResources a -> Semaphore -- | A binary semaphore to synchronize rendering and presenting [$sel:rrRenderFinishedSemaphore:RecycledResources] :: RecycledResources a -> Semaphore -- | Pool for this frame's commands for each of the queue families. (might -- want more than one of these for multithreaded recording) [$sel:rrQueues:RecycledResources] :: RecycledResources a -> Queues CommandPool [$sel:rrData:RecycledResources] :: RecycledResources a -> a initialRecycledResources :: (MonadResource (RIO env), HasVulkan env, HasLogFunc env) => (Queues CommandPool -> rp -> p -> ResourceT (RIO env) rr) -> rp -> p -> ResourceT (RIO env) (RecycledResources rr) timeoutError :: MonadThrow m => String -> m a module Engine.Render renderFrame :: RenderPass rp => (rr -> StageFrameRIO rp p rr st ()) -> (CommandBuffer -> rr -> ("image index" ::: Word32) -> StageFrameRIO rp p rr st ()) -> StageFrameRIO rp p rr st () module Engine.Run runStack :: StageStack -> StageRIO (Maybe SwapchainResources) () run :: RenderPass rp => Maybe SwapchainResources -> ReleaseKey -> Stage rp p rr st -> StageRIO st StageResult step :: RenderPass rp => ReleaseKey -> Stage rp p rr st -> DataRecycler (RecycledResources rr) -> Maybe Int -> Frame rp p rr -> StageRIO st (LoopAction (Frame rp p rr)) module Render.Code -- | A wrapper to show code into compileShaderQ vars. newtype Code Code :: Text -> Code [$sel:unCode:Code] :: Code -> Text -- | glsl is a QuasiQuoter which produces GLSL source code with -- #line directives inserted so that error locations point to -- the correct location in the Haskell source file. It also permits basic -- string interpolation. -- -- -- -- It is intended to be used in concert with compileShaderQ like -- so -- --
--   myConstant = 3.141 -- Note that this will have to be in a different module
--   myFragmentShader = $(compileShaderQ Nothing "frag" Nothing [glsl|
--     #version 450
--     const float myConstant = ${myConstant};
--     main (){
--     }
--   |])
--   
-- -- An explicit example (interactive is from doctest): -- --
--   >>> let version = 450 :: Int in [glsl|#version $version|]
--   "#version 450\n#extension GL_GOOGLE_cpp_style_line_directive : enable\n#line 32 \"<interactive>\"\n"
--   
-- -- Note that line number will be thrown off if any of the interpolated -- variables contain newlines. glsl :: QuasiQuoter -- | Trimmed quasiquoter variation. Same as untrimming, but also -- removes the leading and trailing whitespace. trimming :: QuasiQuoter compileVert :: Code -> Q Exp compileFrag :: Code -> Q Exp compileComp :: Code -> Q Exp targetEnv :: IsString a => a instance Data.String.IsString Render.Code.Code instance GHC.Classes.Ord Render.Code.Code instance GHC.Classes.Eq Render.Code.Code instance GHC.Show.Show Render.Code.Code module Engine.SpirV.Compile glsl :: (HasLogFunc env, HasProcessContext env) => Maybe FilePath -> Text -> Text -> Code -> RIO env () glslStages :: (StageInfo stages, HasLogFunc env, HasProcessContext env) => Maybe FilePath -> Text -> stages (Maybe Code) -> RIO env () glslPipelines :: (StageInfo stages, HasLogFunc env, HasProcessContext env) => Maybe FilePath -> Map Text (stages (Maybe Code)) -> RIO env () module Render.Code.Noise hash33 :: Code module Render.Pass usePass :: (MonadIO io, HasRenderPass a) => a -> Word32 -> CommandBuffer -> io r -> io r setViewportScissor :: (HasRenderPass rp, MonadIO io) => CommandBuffer -> Extent2D -> rp -> io () beginInfo :: HasRenderPass a => a -> Word32 -> RenderPassBeginInfo '[] -- | Compatibility copypasta from the future to derive Applicative without -- incurring dependency and boilerplate from -- Distributive/Representable. module Resource.Collection.Generic -- | Representable types of kind * -> * (or kind k -> -- *, when PolyKinds is enabled). This class is derivable -- in GHC with the DeriveGeneric flag on. -- -- A Generic1 instance must satisfy the following laws: -- --
--   from1 . to1id
--   to1 . from1id
--   
class Generic1 (f :: k -> Type) where { -- | Generic representation type type family Rep1 (f :: k -> Type) :: k -> Type; } -- | Convert from the datatype to its representation from1 :: forall (a :: k). Generic1 f => f a -> Rep1 f a -- | Convert from the representation to the datatype to1 :: forall (a :: k). Generic1 f => Rep1 f a -> f a newtype Generically1 f a [Generically1] :: f a -> Generically1 f a instance (GHC.Generics.Generic1 f, GHC.Base.Functor (GHC.Generics.Rep1 f)) => GHC.Base.Functor (Resource.Collection.Generic.Generically1 f) instance (GHC.Generics.Generic1 f, GHC.Base.Applicative (GHC.Generics.Rep1 f)) => GHC.Base.Applicative (Resource.Collection.Generic.Generically1 f) instance (GHC.Generics.Generic1 f, GHC.Base.Alternative (GHC.Generics.Rep1 f)) => GHC.Base.Alternative (Resource.Collection.Generic.Generically1 f) module Resource.Collection enumerate :: (Traversable t, Num ix) => t a -> t (ix, a) size :: (Foldable t, Num size) => t a -> size toVector :: Foldable collection => collection a -> Vector a toVectorStorable :: (Foldable collection, Storable a) => collection a -> Vector a -- | Representable types of kind * -> * (or kind k -> -- *, when PolyKinds is enabled). This class is derivable -- in GHC with the DeriveGeneric flag on. -- -- A Generic1 instance must satisfy the following laws: -- --
--   from1 . to1id
--   to1 . from1id
--   
class Generic1 (f :: k -> Type) newtype Generically1 f a [Generically1] :: f a -> Generically1 f a instance GHC.Base.Applicative Resource.Collection.Example instance GHC.Generics.Generic1 Resource.Collection.Example instance Data.Traversable.Traversable Resource.Collection.Example instance Data.Foldable.Foldable Resource.Collection.Example instance GHC.Base.Functor Resource.Collection.Example instance GHC.Show.Show a => GHC.Show.Show (Resource.Collection.Example a) instance GHC.Classes.Ord a => GHC.Classes.Ord (Resource.Collection.Example a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Resource.Collection.Example a) module Render.Samplers data Collection a Collection :: a -> a -> a -> a -> a -> a -> a -> a -> Collection a [$sel:linearMipRepeat:Collection] :: Collection a -> a [$sel:linearMip:Collection] :: Collection a -> a [$sel:linearRepeat:Collection] :: Collection a -> a [$sel:linear:Collection] :: Collection a -> a [$sel:nearestMipRepeat:Collection] :: Collection a -> a [$sel:nearestMip:Collection] :: Collection a -> a [$sel:nearestRepeat:Collection] :: Collection a -> a [$sel:nearest:Collection] :: Collection a -> a allocate :: MonadVulkan env io => ("max anisotropy" ::: Float) -> ResourceT io (Collection Sampler) allocateFrom :: (PokeChain e, Extendss SamplerCreateInfo e, MonadVulkan env io) => ("max anisotropy" ::: Float) -> Params -> (SamplerCreateInfo '[] -> SamplerCreateInfo e) -> ResourceT io Sampler indices :: Collection Int32 type Params = (Filter, "LOD clamp" ::: Float, SamplerAddressMode) params :: Collection Params createInfo :: ("max anisotropy" ::: Float) -> Filter -> ("max LoD" ::: Float) -> SamplerAddressMode -> SamplerCreateInfo '[] instance GHC.Base.Applicative Render.Samplers.Collection instance GHC.Generics.Generic1 Render.Samplers.Collection instance Data.Traversable.Traversable Render.Samplers.Collection instance Data.Foldable.Foldable Render.Samplers.Collection instance GHC.Base.Functor Render.Samplers.Collection instance GHC.Show.Show a => GHC.Show.Show (Render.Samplers.Collection a) module Engine.Window.MouseButton type Callback m = (ModifierKeys, MouseButtonState, MouseButton) -> m () callback :: MonadSink rs m => Callback m -> m ReleaseKey -- | Part of the Mouse Input system. data MouseButton MouseButton'1 :: MouseButton MouseButton'2 :: MouseButton MouseButton'3 :: MouseButton MouseButton'4 :: MouseButton MouseButton'5 :: MouseButton MouseButton'6 :: MouseButton MouseButton'7 :: MouseButton MouseButton'8 :: MouseButton -- | If the mouse button is pressed or not when getMouseButton is -- called. data MouseButtonState MouseButtonState'Pressed :: MouseButtonState MouseButtonState'Released :: MouseButtonState -- | Modifier keys that were pressed as part of another keypress event. data ModifierKeys ModifierKeys :: !Bool -> !Bool -> !Bool -> !Bool -> !Bool -> !Bool -> ModifierKeys [modifierKeysShift] :: ModifierKeys -> !Bool [modifierKeysControl] :: ModifierKeys -> !Bool [modifierKeysAlt] :: ModifierKeys -> !Bool [modifierKeysSuper] :: ModifierKeys -> !Bool [modifierKeysCapsLock] :: ModifierKeys -> !Bool [modifierKeysNumLock] :: ModifierKeys -> !Bool mkCallback :: UnliftIO m -> Callback m -> MouseButtonCallback mouseButtonState :: a -> a -> MouseButtonState -> a whenPressed :: Applicative f => MouseButtonState -> f () -> f () whenReleased :: Applicative f => MouseButtonState -> f () -> f () data Collection a Collection :: a -> Collection a [$sel:mb1:Collection, $sel:mb2:Collection, $sel:mb3:Collection, $sel:mb4:Collection, $sel:mb5:Collection, $sel:mb6:Collection, $sel:mb7:Collection, $sel:mb8:Collection] :: Collection a -> a collectionGlfw :: Collection MouseButton atGlfw :: Collection a -> MouseButton -> a instance GHC.Base.Applicative Engine.Window.MouseButton.Collection instance Data.Traversable.Traversable Engine.Window.MouseButton.Collection instance Data.Foldable.Foldable Engine.Window.MouseButton.Collection instance GHC.Base.Functor Engine.Window.MouseButton.Collection instance GHC.Generics.Generic1 Engine.Window.MouseButton.Collection instance GHC.Show.Show a => GHC.Show.Show (Engine.Window.MouseButton.Collection a) instance GHC.Classes.Ord a => GHC.Classes.Ord (Engine.Window.MouseButton.Collection a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Engine.Window.MouseButton.Collection a) module Engine.Events.MouseButton type ClickHandler e st m = Sink e st -> Vec2 -> (ModifierKeys, MouseButtonState, MouseButton) -> m () callback :: (MonadSink rs m, HasOutput cursor, GetOutput cursor ~ Vec2) => cursor -> ClickHandler e st m -> Sink e st -> m ReleaseKey handler :: (MonadSink rs m, HasOutput cursor, GetOutput cursor ~ Vec2) => cursor -> ClickHandler e st m -> Sink e st -> (ModifierKeys, MouseButtonState, MouseButton) -> m () module Engine.Vulkan.Pipeline.Raytrace data Stages a Stages :: a -> a -> a -> a -> a -> a -> Stages a -- | ray generation [$sel:rgen:Stages] :: Stages a -> a -- | ray intersection [$sel:rint:Stages] :: Stages a -> a -- | ray any hit [$sel:rahit:Stages] :: Stages a -> a -- | ray closest hit [$sel:rchit:Stages] :: Stages a -> a -- | ray miss [$sel:rmiss:Stages] :: Stages a -> a -- | ray callable [$sel:rcall:Stages] :: Stages a -> a instance GHC.Base.Applicative Engine.Vulkan.Pipeline.Raytrace.Stages instance GHC.Generics.Generic1 Engine.Vulkan.Pipeline.Raytrace.Stages instance Data.Traversable.Traversable Engine.Vulkan.Pipeline.Raytrace.Stages instance Data.Foldable.Foldable Engine.Vulkan.Pipeline.Raytrace.Stages instance GHC.Base.Functor Engine.Vulkan.Pipeline.Raytrace.Stages instance GHC.Show.Show a => GHC.Show.Show (Engine.Vulkan.Pipeline.Raytrace.Stages a) instance GHC.Classes.Ord a => GHC.Classes.Ord (Engine.Vulkan.Pipeline.Raytrace.Stages a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Engine.Vulkan.Pipeline.Raytrace.Stages a) instance Engine.Vulkan.Pipeline.Stages.StageInfo Engine.Vulkan.Pipeline.Raytrace.Stages module Resource.CommandBuffer allocatePools :: (HasVulkan context, MonadResource m) => context -> m (ReleaseKey, Queues CommandPool) withPools :: (MonadVulkan env m, MonadResource m) => (Queues CommandPool -> m a) -> m a -- | Scratch command buffer for transfer operations. The simple fence makes -- it unusable for rendering. oneshot_ :: (HasVulkan context, MonadUnliftIO m) => context -> Queues CommandPool -> (forall a. Queues a -> a) -> (CommandBuffer -> m ()) -> m () module Resource.Compressed.Zstd newtype Compressed a Compressed :: a -> Compressed a [$sel:getCompressed:Compressed] :: Compressed a -> a compressBytes :: ByteString -> Compressed ByteString decompressBytes :: Compressed ByteString -> Either CompressedError ByteString data CompressedError ZstdError :: Text -> CompressedError EmptyFile :: FilePath -> CompressedError fromFileWith :: MonadIO m => (ByteString -> m b) -> (FilePath -> m b) -> FilePath -> m b loadCompressed :: MonadIO m => (ByteString -> m b) -> FilePath -> m b compressedExts :: [FilePath] instance GHC.Show.Show Resource.Compressed.Zstd.CompressedError instance GHC.Classes.Eq Resource.Compressed.Zstd.CompressedError instance GHC.Exception.Type.Exception Resource.Compressed.Zstd.CompressedError instance Data.Typeable.Internal.Typeable a => GHC.Show.Show (Resource.Compressed.Zstd.Compressed a) module Resource.Image.Atlas -- | Regular grid atlas data Atlas Atlas :: UVec2 -> UVec2 -> UVec2 -> UVec2 -> Vec2 -> Atlas [$sel:sizeTiles:Atlas] :: Atlas -> UVec2 [$sel:sizePx:Atlas] :: Atlas -> UVec2 [$sel:tileSizePx:Atlas] :: Atlas -> UVec2 [$sel:marginPx:Atlas] :: Atlas -> UVec2 [$sel:uvScale:Atlas] :: Atlas -> Vec2 fromTileSize :: UVec2 -> UVec2 -> UVec2 -> Atlas fromImageSize :: UVec2 -> UVec2 -> UVec2 -> Either UVec2 Atlas instance GHC.Generics.Generic Resource.Image.Atlas.Atlas instance GHC.Show.Show Resource.Image.Atlas.Atlas instance GHC.Classes.Eq Resource.Image.Atlas.Atlas module Resource.Region run :: MonadResource m => ResourceT m a -> m (ReleaseKey, a) exec :: MonadResource m => ResourceT m a -> m ReleaseKey eval :: MonadResource m => ResourceT m a -> m a local :: MonadResource m => m (ReleaseKey, a) -> ResourceT m a local_ :: MonadResource m => m ReleaseKey -> ResourceT m () register_ :: MonadUnliftIO m => IO () -> ResourceT m () attach :: MonadUnliftIO m => ReleaseKey -> ResourceT m () attachAsync :: MonadUnliftIO m => Async a -> ResourceT m () logDebug :: (MonadUnliftIO m, MonadReader env m, HasLogFunc env, HasCallStack) => Utf8Builder -> Utf8Builder -> ResourceT m () -- | A lookup key for a specific release action. This value is returned by -- register and allocate, and is passed to -- release. -- -- Since 0.3.0 data ReleaseKey -- | Call a release action early, and deregister it from the list of -- cleanup actions to be performed. -- -- Since 0.3.0 release :: MonadIO m => ReleaseKey -> m () module Engine.Stage.Component assemble :: Foldable t => Text -> Rendering rp p st -> Resources rp p st rr -> t (Scene rp p st rr) -> Stage rp p rr st data Rendering rp p st Rendering :: (SwapchainResources -> ResourceT (StageRIO st) rp) -> (SwapchainResources -> rp -> ResourceT (StageRIO st) p) -> Rendering rp p st [$sel:rAllocateRP:Rendering] :: Rendering rp p st -> SwapchainResources -> ResourceT (StageRIO st) rp [$sel:rAllocateP:Rendering] :: Rendering rp p st -> SwapchainResources -> rp -> ResourceT (StageRIO st) p data NoRenderPass NoRenderPass :: NoRenderPass data NoPipelines NoPipelines :: NoPipelines type NoRendering = Rendering NoRenderPass NoPipelines noRendering :: NoRendering st data Resources rp p st rr Resources :: StageRIO (Maybe SwapchainResources) (ReleaseKey, st) -> (Queues CommandPool -> rp -> p -> ResourceT (StageRIO st) rr) -> Resources rp p st rr [$sel:rInitialRS:Resources] :: Resources rp p st rr -> StageRIO (Maybe SwapchainResources) (ReleaseKey, st) [$sel:rInitialRR:Resources] :: Resources rp p st rr -> Queues CommandPool -> rp -> p -> ResourceT (StageRIO st) rr type NoResources rp p = Resources rp p NoRunState NoFrameResources data NoRunState NoRunState :: NoRunState data NoFrameResources NoFrameResources :: NoFrameResources noResources :: NoResources rp p data Scene rp p st rr Scene :: ResourceT (StageRIO st) () -> (st -> rr -> StageFrameRIO rp p rr st ()) -> (CommandBuffer -> rr -> ("image index" ::: Word32) -> StageFrameRIO rp p rr st ()) -> Scene rp p st rr [$sel:scBeforeLoop:Scene] :: Scene rp p st rr -> ResourceT (StageRIO st) () [$sel:scUpdateBuffers:Scene] :: Scene rp p st rr -> st -> rr -> StageFrameRIO rp p rr st () [$sel:scRecordCommands:Scene] :: Scene rp p st rr -> CommandBuffer -> rr -> ("image index" ::: Word32) -> StageFrameRIO rp p rr st () instance GHC.Base.Semigroup (Engine.Stage.Component.Scene rp p st rr) instance GHC.Base.Monoid (Engine.Stage.Component.Scene rp p st rr) instance Engine.Vulkan.Types.RenderPass Engine.Stage.Component.NoRenderPass module Engine.Stage.Bootstrap.Setup stackStage :: (a -> StackStage) -> StageSetupRIO a -> StackStage bootstrapStage :: (a -> StackStage) -> StageSetupRIO a -> Stage NoRenderPass NoPipelines NoFrameResources NoRunState module Engine.App engineMain :: StackStage -> IO () engineMainWith :: (a -> StackStage) -> StageSetupRIO a -> IO () module Resource.Source data Source Bytes :: Maybe Text -> ByteString -> Source BytesZstd :: Maybe Text -> Compressed ByteString -> Source File :: Maybe Text -> FilePath -> Source load :: forall a m env. (MonadIO m, MonadReader env m, HasLogFunc env, Typeable a, HasCallStack) => (ByteString -> m a) -> Source -> m a embedFile :: FilePath -> Q Exp instance GHC.Records.HasField "label" Resource.Source.Source (GHC.Maybe.Maybe Data.Text.Internal.Text) instance GHC.Show.Show Resource.Source.Source module Resource.Static data Scope Files :: Scope Dirs :: Scope filePaths :: Scope -> FilePath -> Q [Dec] filePatterns :: Scope -> FilePath -> Q [Dec] mkDeclsWith :: (FilePath -> [[String]] -> Q [Dec]) -> Scope -> FilePath -> Q [Dec] getFileListPieces :: Scope -> FilePath -> IO [[String]] instance GHC.Generics.Generic Resource.Static.Scope instance GHC.Enum.Bounded Resource.Static.Scope instance GHC.Enum.Enum Resource.Static.Scope instance GHC.Show.Show Resource.Static.Scope instance GHC.Classes.Ord Resource.Static.Scope instance GHC.Classes.Eq Resource.Static.Scope module Resource.Vulkan.DescriptorLayout create :: MonadVulkan env m => Vector [(DescriptorSetLayoutBinding, DescriptorBindingFlags)] -> m (Vector DescriptorSetLayout) forPipeline :: MonadVulkan env m => Vector DescriptorSetLayout -> Vector PushConstantRange -> m PipelineLayout module Resource.Vulkan.Named object :: (MonadVulkan env m, HasObjectType a) => a -> Text -> m () objectOrigin :: (MonadVulkan env m, HasObjectType a, HasCallStack) => a -> m () module Resource.Vulkan.DescriptorPool allocate :: (MonadVulkan env m, MonadResource m) => Maybe Text -> Word32 -> [(DescriptorType, Word32)] -> m (ReleaseKey, DescriptorPool) allocateSetsFrom :: MonadVulkan env m => DescriptorPool -> Maybe Text -> Vector DescriptorSetLayout -> m (Vector DescriptorSet) module Resource.Buffer data Store Staged :: Store Coherent :: Store data Allocated (s :: Store) a Allocated :: Buffer -> Allocation -> AllocationInfo -> Int -> Word32 -> BufferUsageFlagBits -> Maybe Text -> Allocated (s :: Store) a [$sel:aBuffer:Allocated] :: Allocated (s :: Store) a -> Buffer [$sel:aAllocation:Allocated] :: Allocated (s :: Store) a -> Allocation [$sel:aAllocationInfo:Allocated] :: Allocated (s :: Store) a -> AllocationInfo [$sel:aCapacity:Allocated] :: Allocated (s :: Store) a -> Int [$sel:aUsed:Allocated] :: Allocated (s :: Store) a -> Word32 [$sel:aUsage:Allocated] :: Allocated (s :: Store) a -> BufferUsageFlagBits [$sel:aLabel:Allocated] :: Allocated (s :: Store) a -> Maybe Text allocateCoherent :: (MonadVulkan env m, MonadResource m, Storable a) => Maybe Text -> BufferUsageFlagBits -> ("initial size" ::: Int) -> Vector a -> m (ReleaseKey, Allocated 'Coherent a) createCoherent :: forall a env m. (MonadVulkan env m, Storable a) => Maybe Text -> BufferUsageFlagBits -> ("initial size" ::: Int) -> Vector a -> m (Allocated 'Coherent a) createStaged :: forall a env m. (Storable a, MonadVulkan env m) => Maybe Text -> Queues CommandPool -> BufferUsageFlagBits -> Int -> Vector a -> m (Allocated 'Staged a) register :: (MonadVulkan env m, MonadResource m) => Allocated stage a -> m ReleaseKey destroy :: (MonadUnliftIO io, HasVulkan context) => context -> Allocated s a -> io () peekCoherent :: (MonadIO m, Storable a) => Word32 -> Allocated 'Coherent a -> m (Maybe a) pokeCoherent :: (MonadVulkan env m, Storable a) => Allocated 'Coherent a -> Word32 -> a -> m () updateCoherent :: (MonadUnliftIO io, Storable a) => Vector a -> Allocated 'Coherent a -> io (Allocated 'Coherent a) updateCoherentResize_ :: (MonadVulkan env m, Storable a) => Allocated 'Coherent a -> Vector a -> m (Allocated 'Coherent a) copyBuffer_ :: (MonadUnliftIO io, HasVulkan context) => context -> Queues CommandPool -> ("dstBuffer" ::: Buffer) -> ("srcBuffer" ::: Buffer) -> DeviceSize -> io () type ObserverCoherent a = ObserverIO (Allocated 'Coherent a) newObserverCoherent :: (MonadVulkan env m, Storable a) => ("label" ::: Text) -> BufferUsageFlagBits -> Int -> Vector a -> ResourceT m (ObserverCoherent a) observeCoherentResize_ :: (MonadVulkan env m, HasOutput source, GetOutput source ~ Vector output, Storable output) => source -> ObserverCoherent output -> m () observeCoherentSingle :: (MonadVulkan env m, HasOutput source, GetOutput source ~ output, Storable output) => source -> ObserverCoherent output -> m () instance GHC.Show.Show (Resource.Buffer.Allocated s a) instance Vulkan.Core10.APIConstants.HasObjectType (Resource.Buffer.Allocated s a) -- | Experimental helpers for managing models with multiple instance -- buffers. -- -- Only works with fully-coherent models and atomic stores. Not -- particularly efficient: when any element is changed, everything gets -- fully updated. module Resource.Model.Observer newCoherent :: (VertexBuffers res, MonadVulkan env m) => Int -> Text -> ResourceT m (ObserverIO res) observeCoherent :: (MonadVulkan env m, HasOutput output, UpdateCoherent bufs (GetOutput output)) => output -> ObserverIO bufs -> m () class VertexBuffers a createInitial :: forall env m. (VertexBuffers a, MonadVulkan env m) => Int -> Text -> ResourceT m a createInitial :: forall env m. (VertexBuffers a, Generic a, GVertexBuffers (Rep a), MonadVulkan env m) => Int -> Text -> ResourceT m a destroyCurrent :: forall env. (VertexBuffers a, HasVulkan env) => env -> a -> IO () destroyCurrent :: forall env. (VertexBuffers a, Generic a, GVertexBuffers (Rep a), HasVulkan env) => env -> a -> IO () genericCreateInitial :: (Generic a, GVertexBuffers (Rep a), MonadVulkan env m) => Int -> Text -> ResourceT m a genericDestroyCurrent :: (Generic a, GVertexBuffers (Rep a), HasVulkan env) => env -> a -> IO () class UpdateCoherent bufs stores updateCoherent :: forall env m. (UpdateCoherent bufs stores, MonadVulkan env m) => bufs -> stores -> m bufs updateCoherent :: forall env m. (UpdateCoherent bufs stores, Generic bufs, Generic stores, GUpdateCoherent (Rep bufs) (Rep stores), MonadVulkan env m) => bufs -> stores -> m bufs genericUpdateCoherent :: (Generic bufs, Generic stores, GUpdateCoherent (Rep bufs) (Rep stores), MonadVulkan env m) => bufs -> stores -> m bufs instance Foreign.Storable.Storable a => Resource.Model.Observer.UpdateCoherent (Resource.Buffer.Allocated 'Resource.Buffer.Coherent a) (Data.Vector.Storable.Vector a) instance Resource.Model.Observer.UpdateCoherent ba sa => Resource.Model.Observer.GUpdateCoherent (GHC.Generics.K1 br ba) (GHC.Generics.K1 sr sa) instance Resource.Model.Observer.GUpdateCoherent fb fs => Resource.Model.Observer.GUpdateCoherent (GHC.Generics.M1 c cb fb) (GHC.Generics.M1 c cs fs) instance (Resource.Model.Observer.GUpdateCoherent fbl fsl, Resource.Model.Observer.GUpdateCoherent fbr fsr) => Resource.Model.Observer.GUpdateCoherent (fbl GHC.Generics.:*: fbr) (fsl GHC.Generics.:*: fsr) instance Foreign.Storable.Storable a => Resource.Model.Observer.VertexBuffers (Resource.Buffer.Allocated 'Resource.Buffer.Coherent a) instance Resource.Model.Observer.VertexBuffers a => Resource.Model.Observer.GVertexBuffers (GHC.Generics.K1 r a) instance Resource.Model.Observer.GVertexBuffers f => Resource.Model.Observer.GVertexBuffers (GHC.Generics.D1 c f) instance Resource.Model.Observer.GVertexBuffers f => Resource.Model.Observer.GVertexBuffers (GHC.Generics.C1 c f) instance (Resource.Model.Observer.GVertexBuffers l, Resource.Model.Observer.GVertexBuffers r) => Resource.Model.Observer.GVertexBuffers (l GHC.Generics.:*: r) instance (Resource.Model.Observer.GVertexBuffers f, GHC.Generics.Selector c) => Resource.Model.Observer.GVertexBuffers (GHC.Generics.M1 GHC.Generics.S c f) module Resource.Model.Observer.Example data ExampleF f Example :: HKD f Float -> HKD f Float -> ExampleF f [$sel:x:Example] :: ExampleF f -> HKD f Float [$sel:y:Example] :: ExampleF f -> HKD f Float type Example = ExampleF Identity type ExampleStores = ExampleF Vector type ExampleBuffers = ExampleF (Allocated 'Coherent) -- | Deprecated: Just use Observer.newCoherent new :: ResourceT (StageRIO st) (ObserverIO ExampleBuffers) -- | Deprecated: Just use Observer.updateCoherent update :: MonadVulkan env m => ExampleBuffers -> ExampleStores -> m ExampleBuffers instance GHC.Generics.Generic (Resource.Model.Observer.Example.ExampleF f) instance GHC.Show.Show Resource.Model.Observer.Example.Example instance GHC.Show.Show Resource.Model.Observer.Example.ExampleStores instance GHC.Show.Show Resource.Model.Observer.Example.ExampleBuffers instance Resource.Model.Observer.VertexBuffers Resource.Model.Observer.Example.ExampleBuffers instance Resource.Model.Observer.UpdateCoherent Resource.Model.Observer.Example.ExampleBuffers Resource.Model.Observer.Example.ExampleStores module Resource.Image data AllocatedImage AllocatedImage :: Allocation -> Extent3D -> Format -> Image -> ImageView -> ImageSubresourceRange -> AllocatedImage [$sel:aiAllocation:AllocatedImage] :: AllocatedImage -> Allocation [$sel:aiExtent:AllocatedImage] :: AllocatedImage -> Extent3D [$sel:aiFormat:AllocatedImage] :: AllocatedImage -> Format [$sel:aiImage:AllocatedImage] :: AllocatedImage -> Image [$sel:aiImageView:AllocatedImage] :: AllocatedImage -> ImageView [$sel:aiImageRange:AllocatedImage] :: AllocatedImage -> ImageSubresourceRange allocate :: (MonadVulkan env io, MonadResource io) => Maybe Text -> ImageAspectFlags -> ("image dimensions" ::: Extent3D) -> ("mip levels" ::: Word32) -> ("stored layers" ::: Word32) -> SampleCountFlagBits -> Format -> ImageUsageFlags -> io AllocatedImage allocateView :: (MonadVulkan env m, MonadResource m) => Image -> Format -> ImageSubresourceRange -> m ImageView data DstImage -- | Allocate an image and transition it into TRANSFER_DST_OPTIOMAL allocateDst :: (MonadVulkan env m, MonadResource m) => Queues CommandPool -> Maybe Text -> ("image dimensions" ::: Extent3D) -> ("mip levels" ::: Word32) -> ("stored layers" ::: Word32) -> Format -> m DstImage copyBufferToDst :: (MonadVulkan env m, Integral deviceSize, Foldable t) => Queues CommandPool -> Buffer -> DstImage -> ("mip offsets" ::: t deviceSize) -> m AllocatedImage updateFromStorable :: (Storable a, MonadVulkan env m, MonadResource m) => Queues CommandPool -> AllocatedImage -> Vector a -> m AllocatedImage transitionLayout :: MonadVulkan env m => Queues CommandPool -> Image -> ("mip levels" ::: Word32) -> ("layer count" ::: Word32) -> Format -> ("old" ::: ImageLayout) -> ("new" ::: ImageLayout) -> m () copyBufferToImage :: (Foldable t, Integral deviceSize, MonadVulkan env m) => Queues CommandPool -> Buffer -> Image -> ("base extent" ::: Extent3D) -> ("mip offsets" ::: t deviceSize) -> ("layer count" ::: Word32) -> m () subresource :: ImageAspectFlags -> ("mip levels" ::: Word32) -> ("layer count" ::: Word32) -> ImageSubresourceRange inflateExtent :: Extent2D -> Word32 -> Extent3D instance GHC.Show.Show Resource.Image.AllocatedImage module Resource.Texture data Texture tag Texture :: Format -> Word32 -> Word32 -> AllocatedImage -> Texture tag [$sel:tFormat:Texture] :: Texture tag -> Format [$sel:tMipLevels:Texture] :: Texture tag -> Word32 -- | Actual number of layers, up to ArrayOf a [$sel:tLayers:Texture] :: Texture tag -> Word32 [$sel:tAllocatedImage:Texture] :: Texture tag -> AllocatedImage data TextureError LoadError :: Int64 -> Text -> TextureError LayerError :: Word32 -> Word32 -> TextureError MipLevelsError :: Word32 -> Int -> TextureError ArrayError :: Word32 -> Word32 -> TextureError data Flat data CubeMap data ArrayOf (layers :: Nat) -- | Number of expected texture layers to load from resource. class TextureLayers a textureLayers :: TextureLayers a => Word32 debugNameCollection :: (Traversable t, MonadVulkan env m, HasLogFunc env, HasCallStack) => t (Texture layers) -> t FilePath -> m () type TextureLoader m layers = Format -> Queues CommandPool -> FilePath -> m (Texture layers) createImageView :: (MonadIO io, HasVulkan context) => context -> Image -> Format -> ("mip levels" ::: Word32) -> ("array layers" ::: Word32) -> io ImageView imageCI :: Format -> Extent3D -> Word32 -> Word32 -> ImageCreateInfo '[] imageAllocationCI :: AllocationCreateInfo stageBufferCI :: Integral a => a -> BufferCreateInfo '[] stageAllocationCI :: AllocationCreateInfo withSize2d :: Num i => (i -> i -> a) -> Texture tag -> a withSize3d :: Num i => (i -> i -> i -> a) -> Texture tag -> a instance GHC.Show.Show Resource.Texture.TextureError instance GHC.Classes.Ord Resource.Texture.TextureError instance GHC.Classes.Eq Resource.Texture.TextureError instance GHC.Show.Show (Resource.Texture.Texture tag) instance Resource.Texture.TextureLayers Resource.Texture.CubeMap instance Resource.Texture.TextureLayers Resource.Texture.Flat instance GHC.TypeNats.KnownNat n => Resource.Texture.TextureLayers (Resource.Texture.ArrayOf n) instance GHC.Records.HasField "size" (Resource.Texture.Texture tag) Geomancy.Vec2.Vec2 instance GHC.Exception.Type.Exception Resource.Texture.TextureError module Resource.Texture.Ktx2 load :: (TextureLayers a, MonadVulkan env m, MonadResource m, MonadThrow m, HasLogFunc env, Typeable a, HasCallStack) => Queues CommandPool -> Source -> m (Texture a) loadBytes :: (TextureLayers a, MonadVulkan env m, MonadResource m, MonadThrow m, HasLogFunc env) => Maybe Text -> Queues CommandPool -> ByteString -> m (Texture a) loadKtx2 :: forall a m env src. (TextureLayers a, MonadVulkan env m, MonadResource m, MonadThrow m, HasLogFunc env, ReadChunk src, ReadLevel src) => Maybe Text -> Queues CommandPool -> Context src -> m (Texture a) module Resource.Texture.Ktx1 load :: (TextureLayers a, MonadVulkan env m, MonadResource m, MonadThrow m, HasLogFunc env, Typeable a, HasCallStack) => Queues CommandPool -> Source -> m (Texture a) loadBytes :: (TextureLayers a, MonadVulkan env m, MonadResource m, MonadThrow m, HasLogFunc env) => Queues CommandPool -> ByteString -> m (Texture a) loadKtx1 :: forall a m env. (TextureLayers a, MonadVulkan env m, MonadResource m, MonadThrow m, HasLogFunc env) => Queues CommandPool -> Ktx -> m (Texture a) module Resource.Combined.Textures data Collection textures fonts a Collection :: textures a -> fonts a -> Collection textures fonts a [$sel:textures:Collection] :: Collection textures fonts a -> textures a [$sel:fonts:Collection] :: Collection textures fonts a -> fonts a attachDebugNames :: (Traversable textures, Traversable fonts, MonadVulkan env m, HasLogFunc env, HasCallStack) => Collection textures fonts (Texture a) -> textures FilePath -> fonts FilePath -> m () instance GHC.Generics.Generic (Resource.Combined.Textures.Collection textures fonts a) instance (Data.Traversable.Traversable textures, Data.Traversable.Traversable fonts) => Data.Traversable.Traversable (Resource.Combined.Textures.Collection textures fonts) instance (Data.Foldable.Foldable textures, Data.Foldable.Foldable fonts) => Data.Foldable.Foldable (Resource.Combined.Textures.Collection textures fonts) instance (GHC.Base.Functor textures, GHC.Base.Functor fonts) => GHC.Base.Functor (Resource.Combined.Textures.Collection textures fonts) instance (GHC.Show.Show (textures a), GHC.Show.Show (fonts a)) => GHC.Show.Show (Resource.Combined.Textures.Collection textures fonts a) instance (GHC.Base.Applicative t, GHC.Base.Applicative f) => GHC.Base.Applicative (Resource.Combined.Textures.Collection t f) module Render.Pass.Offscreen data Settings Settings :: Text -> Extent2D -> Format -> Maybe ImageLayout -> Format -> Maybe ImageLayout -> Word32 -> Bool -> SampleCountFlagBits -> Bool -> Settings [$sel:sLabel:Settings] :: Settings -> Text [$sel:sExtent:Settings] :: Settings -> Extent2D [$sel:sFormat:Settings] :: Settings -> Format -- | Target color format when used for export. [$sel:sColorLayout:Settings] :: Settings -> Maybe ImageLayout [$sel:sDepthFormat:Settings] :: Settings -> Format -- | Target depth format when used for export. [$sel:sDepthLayout:Settings] :: Settings -> Maybe ImageLayout [$sel:sLayers:Settings] :: Settings -> Word32 -- | Makes sense only for multiple layers. [$sel:sMultiView:Settings] :: Settings -> Bool -- | Multisample prevents mipmapping and cubes. [$sel:sSamples:Settings] :: Settings -> SampleCountFlagBits [$sel:sMipMap:Settings] :: Settings -> Bool allocate :: (MonadResource m, MonadVulkan env m, HasLogFunc env) => Settings -> m Offscreen data Offscreen Offscreen :: RenderPass -> Extent2D -> AllocatedImage -> AllocatedImage -> Word32 -> Word32 -> Framebuffer -> Rect2D -> Vector ClearValue -> RefCounted -> Offscreen [$sel:oRenderPass:Offscreen] :: Offscreen -> RenderPass [$sel:oExtent:Offscreen] :: Offscreen -> Extent2D [$sel:oColor:Offscreen] :: Offscreen -> AllocatedImage [$sel:oDepth:Offscreen] :: Offscreen -> AllocatedImage [$sel:oLayers:Offscreen] :: Offscreen -> Word32 [$sel:oMipLevels:Offscreen] :: Offscreen -> Word32 [$sel:oFrameBuffer:Offscreen] :: Offscreen -> Framebuffer [$sel:oRenderArea:Offscreen] :: Offscreen -> Rect2D [$sel:oClear:Offscreen] :: Offscreen -> Vector ClearValue [$sel:oRelease:Offscreen] :: Offscreen -> RefCounted colorTexture :: Offscreen -> Texture Flat colorCube :: Offscreen -> Texture CubeMap depthTexture :: Offscreen -> Texture Flat depthCube :: Offscreen -> Texture CubeMap instance GHC.Show.Show Render.Pass.Offscreen.Settings instance GHC.Classes.Eq Render.Pass.Offscreen.Settings instance Engine.Vulkan.Types.HasRenderPass Render.Pass.Offscreen.Offscreen instance Engine.Vulkan.Types.RenderPass Render.Pass.Offscreen.Offscreen module Engine.Vulkan.Shader data Shader Shader :: Vector ShaderModule -> Vector (SomeStruct PipelineShaderStageCreateInfo) -> Shader [$sel:sModules:Shader] :: Shader -> Vector ShaderModule [$sel:sPipelineStages:Shader] :: Shader -> Vector (SomeStruct PipelineShaderStageCreateInfo) create :: (MonadVulkan env io, StageInfo t, HasCallStack) => t (Maybe ByteString) -> Maybe SpecializationInfo -> io Shader destroy :: MonadVulkan env io => Shader -> io () withSpecialization :: (Specialization spec, MonadUnliftIO m) => spec -> (Maybe SpecializationInfo -> m a) -> m a class Specialization a specializationData :: Specialization a => a -> [Word32] class SpecializationConst a packConstData :: SpecializationConst a => a -> Word32 instance Engine.Vulkan.Shader.Specialization GHC.Word.Word32 instance Engine.Vulkan.Shader.Specialization GHC.Int.Int32 instance Engine.Vulkan.Shader.Specialization GHC.Types.Float instance Engine.Vulkan.Shader.Specialization GHC.Types.Bool instance Engine.Vulkan.Shader.SpecializationConst GHC.Word.Word32 instance Engine.Vulkan.Shader.SpecializationConst GHC.Int.Int32 instance Engine.Vulkan.Shader.SpecializationConst GHC.Types.Float instance Engine.Vulkan.Shader.SpecializationConst GHC.Types.Bool instance (Engine.Vulkan.Shader.SpecializationConst a, Engine.Vulkan.Shader.SpecializationConst b) => Engine.Vulkan.Shader.Specialization (a, b) instance (Engine.Vulkan.Shader.SpecializationConst a, Engine.Vulkan.Shader.SpecializationConst b, Engine.Vulkan.Shader.SpecializationConst c) => Engine.Vulkan.Shader.Specialization (a, b, c) instance (Engine.Vulkan.Shader.SpecializationConst a, Engine.Vulkan.Shader.SpecializationConst b, Engine.Vulkan.Shader.SpecializationConst c, Engine.Vulkan.Shader.SpecializationConst d) => Engine.Vulkan.Shader.Specialization (a, b, c, d) instance (Engine.Vulkan.Shader.SpecializationConst a, Engine.Vulkan.Shader.SpecializationConst b, Engine.Vulkan.Shader.SpecializationConst c, Engine.Vulkan.Shader.SpecializationConst d, Engine.Vulkan.Shader.SpecializationConst e) => Engine.Vulkan.Shader.Specialization (a, b, c, d, e) instance (Engine.Vulkan.Shader.SpecializationConst a, Engine.Vulkan.Shader.SpecializationConst b, Engine.Vulkan.Shader.SpecializationConst c, Engine.Vulkan.Shader.SpecializationConst d, Engine.Vulkan.Shader.SpecializationConst e, Engine.Vulkan.Shader.SpecializationConst f) => Engine.Vulkan.Shader.Specialization (a, b, c, d, e, f) instance Engine.Vulkan.Shader.Specialization () instance Engine.Vulkan.Shader.Specialization [GHC.Word.Word32] module Engine.Vulkan.Pipeline.Graphics data Config (dsl :: [Type]) vertices instances spec Config :: StageSpirv -> Maybe StageReflect -> SomeStruct PipelineVertexInputStateCreateInfo -> Tagged dsl [DsLayoutBindings] -> Vector PushConstantRange -> Bool -> Bool -> Bool -> CompareOp -> PrimitiveTopology -> CullModeFlagBits -> Maybe ("constant" ::: Float, "slope" ::: Float) -> spec -> Config (dsl :: [Type]) vertices instances spec [$sel:cStages:Config] :: Config (dsl :: [Type]) vertices instances spec -> StageSpirv [$sel:cReflect:Config] :: Config (dsl :: [Type]) vertices instances spec -> Maybe StageReflect [$sel:cVertexInput:Config] :: Config (dsl :: [Type]) vertices instances spec -> SomeStruct PipelineVertexInputStateCreateInfo [$sel:cDescLayouts:Config] :: Config (dsl :: [Type]) vertices instances spec -> Tagged dsl [DsLayoutBindings] [$sel:cPushConstantRanges:Config] :: Config (dsl :: [Type]) vertices instances spec -> Vector PushConstantRange [$sel:cBlend:Config] :: Config (dsl :: [Type]) vertices instances spec -> Bool [$sel:cDepthWrite:Config] :: Config (dsl :: [Type]) vertices instances spec -> Bool [$sel:cDepthTest:Config] :: Config (dsl :: [Type]) vertices instances spec -> Bool [$sel:cDepthCompare:Config] :: Config (dsl :: [Type]) vertices instances spec -> CompareOp [$sel:cTopology:Config] :: Config (dsl :: [Type]) vertices instances spec -> PrimitiveTopology [$sel:cCull:Config] :: Config (dsl :: [Type]) vertices instances spec -> CullModeFlagBits [$sel:cDepthBias:Config] :: Config (dsl :: [Type]) vertices instances spec -> Maybe ("constant" ::: Float, "slope" ::: Float) [$sel:cSpecialization:Config] :: Config (dsl :: [Type]) vertices instances spec -> spec -- | Settings for generic triangle-rendering pipeline. baseConfig :: Config '[] vertices instances () type family Configure pipeline type family Specialization pipeline vertexInput :: forall a pipeLayout vertices instances. (a ~ Pipeline pipeLayout vertices instances, HasVertexInputBindings vertices, HasVertexInputBindings instances) => SomeStruct PipelineVertexInputStateCreateInfo formatSize :: Integral a => Format -> a pushPlaceholder :: PushConstantRange data Stages a Stages :: a -> a -> a -> a -> a -> Stages a -- | vertex [$sel:vert:Stages] :: Stages a -> a -- | tessellation control [$sel:tesc:Stages] :: Stages a -> a -- | tessellation evaluation [$sel:tese:Stages] :: Stages a -> a -- | geometry [$sel:geom:Stages] :: Stages a -> a -- | fragment [$sel:frag:Stages] :: Stages a -> a stageNames :: (StageInfo t, IsString label) => t label stageFlagBits :: StageInfo t => t ShaderStageFlagBits basicStages :: ("vert" ::: a) -> ("frag" ::: a) -> Stages (Maybe a) vertexOnly :: ("vert" ::: a) -> Stages (Maybe a) type StageCode = Stages (Maybe Code) type StageSpirv = Stages (Maybe ByteString) type StageReflect = Reflect Stages data Pipeline (dsl :: [Type]) vertices instances Pipeline :: Pipeline -> Tagged dsl PipelineLayout -> Tagged dsl DsLayouts -> Pipeline (dsl :: [Type]) vertices instances [$sel:pipeline:Pipeline] :: Pipeline (dsl :: [Type]) vertices instances -> Pipeline [$sel:pLayout:Pipeline] :: Pipeline (dsl :: [Type]) vertices instances -> Tagged dsl PipelineLayout [$sel:pDescLayouts:Pipeline] :: Pipeline (dsl :: [Type]) vertices instances -> Tagged dsl DsLayouts allocate :: (config ~ Configure pipeline, pipeline ~ Pipeline dsl vertices instances, spec ~ Specialization pipeline, Specialization spec, HasCallStack, MonadVulkan env m, MonadResource m, HasRenderPass renderpass) => Maybe Extent2D -> SampleCountFlagBits -> Config dsl vertices instances spec -> renderpass -> m (ReleaseKey, pipeline) create :: (MonadVulkan env io, HasRenderPass renderpass, Specialization spec, HasCallStack) => Maybe Extent2D -> SampleCountFlagBits -> renderpass -> Config dsl vertices instances spec -> io (Pipeline dsl vertices instances) bind :: (Compatible pipeLayout boundLayout, MonadIO m) => CommandBuffer -> Pipeline pipeLayout vertices instances -> Bound boundLayout vertices instances m () -> Bound boundLayout oldVertices oldInstances m () class HasVertexInputBindings a vertexInputBindings :: HasVertexInputBindings a => [VertexInputBinding] vertexFormat :: forall a. HasVkFormat a => VertexInputBinding instanceFormat :: forall a. HasVkFormat a => VertexInputBinding instance GHC.Base.Applicative Engine.Vulkan.Pipeline.Graphics.Stages instance GHC.Generics.Generic1 Engine.Vulkan.Pipeline.Graphics.Stages instance Data.Traversable.Traversable Engine.Vulkan.Pipeline.Graphics.Stages instance Data.Foldable.Foldable Engine.Vulkan.Pipeline.Graphics.Stages instance GHC.Base.Functor Engine.Vulkan.Pipeline.Graphics.Stages instance GHC.Show.Show a => GHC.Show.Show (Engine.Vulkan.Pipeline.Graphics.Stages a) instance GHC.Classes.Ord a => GHC.Classes.Ord (Engine.Vulkan.Pipeline.Graphics.Stages a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Engine.Vulkan.Pipeline.Graphics.Stages a) instance Engine.Vulkan.Pipeline.Graphics.HasVertexInputBindings () instance Engine.Vulkan.Pipeline.Graphics.HasVertexInputBindings Geomancy.Transform.Transform instance Engine.Vulkan.Pipeline.Stages.StageInfo Engine.Vulkan.Pipeline.Graphics.Stages module Resource.Model data Indexed storage pos attrs Indexed :: Maybe Text -> Allocated storage pos -> Allocated storage attrs -> Allocated storage Word32 -> Indexed storage pos attrs [$sel:iLabel:Indexed] :: Indexed storage pos attrs -> Maybe Text [$sel:iPositions:Indexed] :: Indexed storage pos attrs -> Allocated storage pos [$sel:iAttrs:Indexed] :: Indexed storage pos attrs -> Allocated storage attrs [$sel:iIndices:Indexed] :: Indexed storage pos attrs -> Allocated storage Word32 type Vertex2d attrs = Vertex Vec2 attrs type Vertex3d attrs = Vertex Packed attrs data Vertex pos attrs Vertex :: pos -> attrs -> Vertex pos attrs [$sel:vPosition:Vertex] :: Vertex pos attrs -> pos [$sel:vAttrs:Vertex] :: Vertex pos attrs -> attrs vertexAttrs :: (pos -> a -> b) -> [Vertex pos a] -> [Vertex pos b] vertexAttrsPos :: (pos -> a) -> [pos] -> [Vertex pos a] class HasVertexBuffers a where { type VertexBuffersOf a; } getVertexBuffers :: HasVertexBuffers a => a -> [Buffer] getInstanceCount :: HasVertexBuffers a => a -> Word32 getVertexBuffers :: (HasVertexBuffers a, Generic a, GHasVertexBuffers (Rep a)) => a -> [Buffer] getInstanceCount :: (HasVertexBuffers a, Generic a, GHasVertexBuffers (Rep a)) => a -> Word32 genericGetVertexBuffers :: (Generic a, GHasVertexBuffers (Rep a)) => a -> [Buffer] genericGetInstanceCount :: (Generic a, GHasVertexBuffers (Rep a)) => a -> Word32 class GHasVertexBuffers f gVertexBuffers :: forall a. GHasVertexBuffers f => f a -> [Buffer] gInstanceCount :: forall a. GHasVertexBuffers f => f a -> Word32 data IndexRange IndexRange :: Word32 -> Word32 -> IndexRange [$sel:irFirstIndex:IndexRange] :: IndexRange -> Word32 [$sel:irIndexCount:IndexRange] :: IndexRange -> Word32 createStagedL :: (MonadVulkan env m, Storable pos, Storable attrs) => Maybe Text -> Queues CommandPool -> [Vertex pos attrs] -> Maybe [Word32] -> m (Indexed 'Staged pos attrs) createStaged :: (MonadVulkan env m, Storable pos, Storable attrs) => Maybe Text -> Queues CommandPool -> Vector pos -> Vector attrs -> Vector Word32 -> m (Indexed 'Staged pos attrs) createCoherentEmpty :: (MonadVulkan env m, Storable pos, Storable attrs) => Maybe Text -> Int -> m (Indexed 'Coherent pos attrs) registerIndexed_ :: (MonadVulkan env m, MonadResource m) => Indexed storage pos attrs -> m () destroyIndexed :: MonadVulkan env m => Indexed storage pos attrs -> m () updateCoherent :: (MonadVulkan env m, Storable pos, Storable attrs) => [Vertex pos attrs] -> Indexed 'Coherent pos attrs -> m (Indexed 'Coherent pos attrs) instance GHC.Show.Show (Resource.Model.Indexed storage pos attrs) instance Data.Traversable.Traversable (Resource.Model.Vertex pos) instance Data.Foldable.Foldable (Resource.Model.Vertex pos) instance GHC.Base.Functor (Resource.Model.Vertex pos) instance (GHC.Show.Show pos, GHC.Show.Show attrs) => GHC.Show.Show (Resource.Model.Vertex pos attrs) instance (GHC.Classes.Ord pos, GHC.Classes.Ord attrs) => GHC.Classes.Ord (Resource.Model.Vertex pos attrs) instance (GHC.Classes.Eq pos, GHC.Classes.Eq attrs) => GHC.Classes.Eq (Resource.Model.Vertex pos attrs) instance GHC.Generics.Generic Resource.Model.IndexRange instance GHC.Show.Show Resource.Model.IndexRange instance GHC.Classes.Ord Resource.Model.IndexRange instance GHC.Classes.Eq Resource.Model.IndexRange instance Codec.Serialise.Class.Serialise Resource.Model.IndexRange instance Foreign.Storable.Storable Resource.Model.IndexRange instance Resource.Model.HasVertexBuffers () instance Resource.Model.HasVertexBuffers (Resource.Buffer.Allocated store a) instance Resource.Model.HasVertexBuffers a => Resource.Model.GHasVertexBuffers (GHC.Generics.K1 r a) instance Resource.Model.GHasVertexBuffers f => Resource.Model.GHasVertexBuffers (GHC.Generics.M1 c cb f) instance (Resource.Model.GHasVertexBuffers l, Resource.Model.GHasVertexBuffers r) => Resource.Model.GHasVertexBuffers (l GHC.Generics.:*: r) instance (Engine.Vulkan.Format.HasVkFormat pos, Engine.Vulkan.Format.HasVkFormat attrs) => Engine.Vulkan.Pipeline.Graphics.HasVertexInputBindings (Resource.Model.Vertex pos attrs) module Resource.Mesh.Types data AxisAligned a AxisAligned :: a -> a -> a -> AxisAligned a [$sel:aaX:AxisAligned] :: AxisAligned a -> a [$sel:aaY:AxisAligned] :: AxisAligned a -> a [$sel:aaZ:AxisAligned] :: AxisAligned a -> a data Meta Meta :: IndexRange -> IndexRange -> IndexRange -> IndexRange -> Vec4 -> Transform -> AxisAligned Measurements -> Meta [$sel:mOpaqueIndices:Meta] :: Meta -> IndexRange [$sel:mBlendedIndices:Meta] :: Meta -> IndexRange [$sel:mOpaqueNodes:Meta] :: Meta -> IndexRange [$sel:mBlendedNodes:Meta] :: Meta -> IndexRange [$sel:mBoundingSphere:Meta] :: Meta -> Vec4 [$sel:mTransformBB:Meta] :: Meta -> Transform [$sel:mMeasurements:Meta] :: Meta -> AxisAligned Measurements data NodeGroup NodeOpaque :: NodeGroup NodeBlended :: NodeGroup data NodePartitions a NodePartitions :: a -> a -> NodePartitions a [$sel:npOpaque:NodePartitions] :: NodePartitions a -> a [$sel:npBlended:NodePartitions] :: NodePartitions a -> a type Nodes = Vector Node data Node Node :: Vec4 -> Transform -> IndexRange -> AxisAligned Measurements -> Node [$sel:nBoundingSphere:Node] :: Node -> Vec4 [$sel:nTransformBB:Node] :: Node -> Transform [$sel:nRange:Node] :: Node -> IndexRange [$sel:nMeasurements:Node] :: Node -> AxisAligned Measurements type TexturedNodes = Vector TexturedNode data TexturedNode TexturedNode :: Node -> TextureParams -> TextureParams -> TextureParams -> TextureParams -> TextureParams -> TexturedNode [$sel:tnNode:TexturedNode] :: TexturedNode -> Node [$sel:tnBase:TexturedNode] :: TexturedNode -> TextureParams [$sel:tnEmissive:TexturedNode] :: TexturedNode -> TextureParams [$sel:tnNormal:TexturedNode] :: TexturedNode -> TextureParams [$sel:tnOcclusion:TexturedNode] :: TexturedNode -> TextureParams [$sel:tnMetallicRoughness:TexturedNode] :: TexturedNode -> TextureParams data TextureParams TextureParams :: Vec2 -> Vec2 -> Vec4 -> Int32 -> Int32 -> TextureParams [$sel:tpScale:TextureParams] :: TextureParams -> Vec2 [$sel:tpOffset:TextureParams] :: TextureParams -> Vec2 [$sel:tpGamma:TextureParams] :: TextureParams -> Vec4 [$sel:tpSamplerId:TextureParams] :: TextureParams -> Int32 [$sel:tpTextureId:TextureParams] :: TextureParams -> Int32 data Measurements Measurements :: Float -> Float -> Float -> Float -> Measurements [$sel:mMin:Measurements] :: Measurements -> Float [$sel:mMax:Measurements] :: Measurements -> Float [$sel:mMean:Measurements] :: Measurements -> Float [$sel:mStd:Measurements] :: Measurements -> Float measureAa :: Foldable t => t Packed -> AxisAligned Measurements measureAaWith :: (Foldable outer, Foldable inner) => (a -> inner Packed) -> outer a -> AxisAligned Measurements middle :: Measurements -> Float middleAa :: AxisAligned Measurements -> AxisAligned Float size :: Measurements -> Float sizeAa :: AxisAligned Measurements -> AxisAligned Float class HasRange a getRange :: HasRange a => a -> IndexRange adjustRange :: HasRange a => a -> Word32 -> a -- | CBOR.encode helper for storable types (vectors, etc.) encodeStorable :: forall a. Storable a => a -> Encoding -- | CBOR.decode helper for storable types (vectors, etc.) decodeStorable :: forall a s. (Storable a, Typeable a) => Decoder s a instance GHC.Generics.Generic (Resource.Mesh.Types.AxisAligned a) instance Data.Traversable.Traversable Resource.Mesh.Types.AxisAligned instance Data.Foldable.Foldable Resource.Mesh.Types.AxisAligned instance GHC.Base.Functor Resource.Mesh.Types.AxisAligned instance GHC.Show.Show a => GHC.Show.Show (Resource.Mesh.Types.AxisAligned a) instance GHC.Classes.Ord a => GHC.Classes.Ord (Resource.Mesh.Types.AxisAligned a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Resource.Mesh.Types.AxisAligned a) instance GHC.Enum.Bounded Resource.Mesh.Types.NodeGroup instance GHC.Enum.Enum Resource.Mesh.Types.NodeGroup instance GHC.Show.Show Resource.Mesh.Types.NodeGroup instance GHC.Classes.Ord Resource.Mesh.Types.NodeGroup instance GHC.Classes.Eq Resource.Mesh.Types.NodeGroup instance Data.Traversable.Traversable Resource.Mesh.Types.NodePartitions instance Data.Foldable.Foldable Resource.Mesh.Types.NodePartitions instance GHC.Base.Functor Resource.Mesh.Types.NodePartitions instance GHC.Show.Show a => GHC.Show.Show (Resource.Mesh.Types.NodePartitions a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Resource.Mesh.Types.NodePartitions a) instance GHC.Generics.Generic Resource.Mesh.Types.TextureParams instance GHC.Show.Show Resource.Mesh.Types.TextureParams instance GHC.Classes.Eq Resource.Mesh.Types.TextureParams instance GHC.Generics.Generic Resource.Mesh.Types.Measurements instance GHC.Show.Show Resource.Mesh.Types.Measurements instance GHC.Classes.Ord Resource.Mesh.Types.Measurements instance GHC.Classes.Eq Resource.Mesh.Types.Measurements instance GHC.Generics.Generic Resource.Mesh.Types.Node instance GHC.Show.Show Resource.Mesh.Types.Node instance GHC.Generics.Generic Resource.Mesh.Types.TexturedNode instance GHC.Show.Show Resource.Mesh.Types.TexturedNode instance GHC.Classes.Eq Resource.Mesh.Types.TexturedNode instance GHC.Generics.Generic Resource.Mesh.Types.Meta instance GHC.Show.Show Resource.Mesh.Types.Meta instance Resource.Mesh.Types.HasRange Resource.Mesh.Types.Node instance Resource.Mesh.Types.HasRange Resource.Mesh.Types.TexturedNode instance Foreign.Storable.Generic.Internal.GStorable Resource.Mesh.Types.Meta instance GHC.Classes.Eq Resource.Mesh.Types.Meta instance Codec.Serialise.Class.Serialise Resource.Mesh.Types.Meta instance Foreign.Storable.Generic.Internal.GStorable Resource.Mesh.Types.TexturedNode instance GHC.Classes.Eq Resource.Mesh.Types.Node instance Foreign.Storable.Generic.Internal.GStorable Resource.Mesh.Types.Node instance Foreign.Storable.Storable Resource.Mesh.Types.Measurements instance Codec.Serialise.Class.Serialise Resource.Mesh.Types.Measurements instance Vulkan.Zero.Zero Resource.Mesh.Types.TextureParams instance Foreign.Storable.Storable Resource.Mesh.Types.TextureParams instance GHC.Base.Applicative Resource.Mesh.Types.AxisAligned instance Foreign.Storable.Storable a => Foreign.Storable.Storable (Resource.Mesh.Types.AxisAligned a) instance Codec.Serialise.Class.Serialise a => Codec.Serialise.Class.Serialise (Resource.Mesh.Types.AxisAligned a) module Resource.Mesh.Utils aabbTranslate :: AxisAligned Measurements -> Transform aabbScale :: AxisAligned Measurements -> Transform boundingSphere :: AxisAligned Measurements -> Vec4 module Resource.Mesh.Codec pattern VER_BREAKS :: Word8 pattern VER_TWEAKS :: Word8 encodeFile :: forall vp vi va vn attrs nodes meta env. (Vector vp Packed, Vector vi Word32, Vector va attrs, Vector vn nodes, Storable attrs, Storable nodes, Serialise meta, HasLogFunc env) => FilePath -> vp Packed -> vi Word32 -> va attrs -> vn nodes -> meta -> RIO env () encodeItems :: (Storable a, Vector v a, MonadIO m) => v a -> m (ByteString, ByteString) encodeCBOR :: Serialise a => a -> (Int, ByteString, ByteString) loadIndexed :: (Storable attrs, Storable nodes, Serialise meta, Show meta, Typeable nodes, HasLogFunc env, MonadResource m, MonadVulkan env m) => Queues CommandPool -> FilePath -> m (ReleaseKey, (meta, Vector nodes, Indexed 'Staged Packed attrs)) loadBlobs :: forall attrs env nodes meta m. (Storable attrs, Serialise meta, Storable nodes, Typeable nodes, HasLogFunc env, MonadReader env m, MonadIO m) => FilePath -> m (meta, Vector nodes, (Vector Packed, Vector Word32, Vector attrs)) decodeItems :: forall item m. (Storable item, MonadFail m) => String -> ByteString -> Maybe Int -> ByteString -> m (Vector item) decodeCBOR :: (Serialise a, MonadFail m) => String -> ByteString -> Int -> ByteString -> m a guardEq :: (MonadFail m, Show a, Eq a) => String -> a -> a -> m () module Render.Draw -- | Single triangle, binding nothing. triangle_ :: MonadUnliftIO m => CommandBuffer -> Bound dsl () () m () -- | Multiple shader-driven triangles without bindings. triangles_ :: MonadUnliftIO m => CommandBuffer -> Word32 -> Bound dsl () () m () -- | Instanced quads. quads :: MonadUnliftIO m => CommandBuffer -> Allocated stage instances -> Bound dsl () instances m () -- | Draw whole-model instances. indexed :: (MonadUnliftIO m, HasVertexBuffers instances) => CommandBuffer -> Indexed storage pos attrs -> instances -> Bound dsl (Vertex pos attrs) (VertexBuffersOf instances) m () -- | Draw subrange of each instance. -- -- E.g. chunks of the same material drawn in different places. indexedRanges :: (MonadUnliftIO m, HasVertexBuffers instances) => CommandBuffer -> Indexed storage pos attrs -> instances -> [IndexRange] -> Bound dsl (Vertex pos attrs) (VertexBuffersOf instances) m () -- | Draw ranges and instances zipped. -- -- E.g. range materials stored in instances. indexedParts :: (MonadUnliftIO m, HasVertexBuffers instances, Foldable t) => Bool -> CommandBuffer -> Indexed storage pos attrs -> instances -> Int -> t IndexRange -> Bound dsl (Vertex pos attrs) (VertexBuffersOf instances) m () -- | Draw whole-model instances, ignoring attributes. indexedPos :: (MonadUnliftIO m, HasVertexBuffers instances) => CommandBuffer -> Indexed storage pos unusedAttrs -> instances -> Bound dsl (Vertex pos ignoreAttrs) (VertexBuffersOf instances) m () -- | Draw subrange of each instances, ignoring attributes. indexedPosRanges :: (MonadUnliftIO m, HasVertexBuffers instances) => CommandBuffer -> Indexed storage pos unusedAttrs -> instances -> [IndexRange] -> Bound dsl (Vertex pos ignoreAttrs) (VertexBuffersOf instances) m () -- | Common unchecked part for pos/attrs unsafeIndexedRanges :: (MonadUnliftIO io, HasVertexBuffers instances, Foldable t) => Bool -> CommandBuffer -> Indexed storage pos attrs -> instances -> t IndexRange -> io () -- | Instance/range zipped unsafeIndexedParts :: (MonadUnliftIO io, HasVertexBuffers instances, Foldable t) => Bool -> CommandBuffer -> Indexed storage pos attrs -> instances -> Int -> t IndexRange -> io () module Engine.Vulkan.Pipeline.Compute data Config (dsl :: [Type]) spec Config :: ByteString -> Tagged dsl [DsLayoutBindings] -> Vector PushConstantRange -> spec -> Config (dsl :: [Type]) spec [$sel:cComputeCode:Config] :: Config (dsl :: [Type]) spec -> ByteString [$sel:cDescLayouts:Config] :: Config (dsl :: [Type]) spec -> Tagged dsl [DsLayoutBindings] [$sel:cPushConstantRanges:Config] :: Config (dsl :: [Type]) spec -> Vector PushConstantRange [$sel:cSpecialization:Config] :: Config (dsl :: [Type]) spec -> spec type family Configure pipeline spec newtype Stages a Stages :: a -> Stages a -- | compute [$sel:comp:Stages] :: Stages a -> a stageNames :: (StageInfo t, IsString label) => t label stageFlagBits :: StageInfo t => t ShaderStageFlagBits type StageCode = Stages (Maybe Code) type StageSpirv = Stages (Maybe ByteString) type StageReflect = Reflect Stages data Pipeline (dsl :: [Type]) vertices instances Pipeline :: Pipeline -> Tagged dsl PipelineLayout -> Tagged dsl DsLayouts -> Pipeline (dsl :: [Type]) vertices instances [$sel:pipeline:Pipeline] :: Pipeline (dsl :: [Type]) vertices instances -> Pipeline [$sel:pLayout:Pipeline] :: Pipeline (dsl :: [Type]) vertices instances -> Tagged dsl PipelineLayout [$sel:pDescLayouts:Pipeline] :: Pipeline (dsl :: [Type]) vertices instances -> Tagged dsl DsLayouts allocate :: (MonadVulkan env m, MonadResource m, HasCallStack, Specialization spec) => Config dsl spec -> m (ReleaseKey, Pipeline dsl Compute Compute) create :: (MonadVulkan env io, Specialization spec, HasCallStack) => Config dsl spec -> io (Pipeline dsl Compute Compute) bind :: (Compatible pipeLayout boundLayout, MonadIO m) => CommandBuffer -> Pipeline pipeLayout Compute Compute -> Bound boundLayout Compute Compute m () -> Bound boundLayout noVertices noInstances m () data Compute instance GHC.Base.Applicative Engine.Vulkan.Pipeline.Compute.Stages instance GHC.Generics.Generic1 Engine.Vulkan.Pipeline.Compute.Stages instance Data.Traversable.Traversable Engine.Vulkan.Pipeline.Compute.Stages instance Data.Foldable.Foldable Engine.Vulkan.Pipeline.Compute.Stages instance GHC.Base.Functor Engine.Vulkan.Pipeline.Compute.Stages instance GHC.Show.Show a => GHC.Show.Show (Engine.Vulkan.Pipeline.Compute.Stages a) instance GHC.Classes.Ord a => GHC.Classes.Ord (Engine.Vulkan.Pipeline.Compute.Stages a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Engine.Vulkan.Pipeline.Compute.Stages a) instance Engine.Vulkan.Pipeline.Stages.StageInfo Engine.Vulkan.Pipeline.Compute.Stages module Engine.Vulkan.Pipeline.External type Process config = Timed () config spawn :: (Foldable stages, MonadReader env m, HasLogFunc env, MonadResource m, MonadUnliftIO m) => (stages (Maybe FilePath) -> m stuff) -> Text -> stages (Maybe FilePath) -> (stuff -> config) -> m (Process config) spawnReflect :: (MonadResource m, MonadUnliftIO m, MonadReader env m, HasLogFunc env, StageInfo stages) => Text -> stages (Maybe FilePath) -> ((stages (Maybe ByteString), Reflect stages) -> config) -> m (Process config) loadConfig :: (Traversable stages, MonadIO io) => stages (Maybe FilePath) -> io (stages (Maybe ByteString)) loadConfigReflect :: (StageInfo stages, MonadIO io, MonadReader env io, HasLogFunc env) => stages (Maybe FilePath) -> io (stages (Maybe ByteString), Reflect stages) type Observer pipeline = ObserverIO (ReleaseKey, pipeline) newObserverGraphics :: (pipeline ~ Pipeline dsl vertices instances, HasOutput worker, Specialization (Specialization pipeline), HasRenderPass renderpass, GetOutput worker ~ Configure pipeline) => renderpass -> SampleCountFlagBits -> worker -> ResourceT (StageRIO rs) (Observer pipeline) observeGraphics :: (HasRenderPass renderpass, HasOutput output, GetOutput output ~ Configure pipeline, pipeline ~ Pipeline dsl vertices instances, spec ~ Specialization pipeline, Specialization spec) => renderpass -> SampleCountFlagBits -> Tagged dsl [DsLayoutBindings] -> output -> ObserverIO (ReleaseKey, pipeline) -> StageFrameRIO rp p fr rs () newObserverCompute :: (config ~ Configure pipeline (), pipeline ~ Pipeline dsl Compute Compute) => Process config -> ResourceT (StageRIO rs) (Observer pipeline) observeCompute :: (HasOutput output, GetOutput output ~ config, Specialization spec, config ~ Configure pipeline spec, pipeline ~ Pipeline dsl Compute Compute) => Tagged dsl [DsLayoutBindings] -> output -> ObserverIO (ReleaseKey, pipeline) -> StageFrameRIO rp p fr rs () type family f ^ p data ConfigureGraphics p data ConfigureCompute p data Observers p observeField :: forall pf p renderpass dsl s vs is rps ps fr rs. (p ~ Pipeline s vs is, Specialization (Specialization p), HasRenderPass renderpass) => renderpass -> SampleCountFlagBits -> Tagged dsl DsLayoutBindings -> pf ConfigureGraphics -> pf Observers -> (forall a. pf a -> a ^ p) -> StageFrameRIO rps ps fr rs () dumpPipelines :: StageInfo t => MonadIO io => FilePath -> Map Text (t (Maybe Code)) -> io ()