Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- type CompiledShader os s = s -> Render os ()
- data Drawcall s = Drawcall {
- drawcallFbo :: s -> (Either WinId (IO FBOKeys, IO ()), IO ())
- feedbackBuffer :: Maybe (s -> IO (GLuint, GLuint, GLuint, GLuint))
- primitiveName :: Int
- rasterizationName :: Maybe Int
- vertexSource :: Text
- optionalGeometrySource :: Maybe Text
- optionalFragmentSource :: Maybe Text
- usedInputs :: [Int]
- usedVUniforms :: [UniformId]
- usedVSamplers :: [SamplerId]
- usedGUniforms :: [UniformId]
- usedGSamplers :: [SamplerId]
- usedFUniforms :: [UniformId]
- usedFSamplers :: [SamplerId]
- primStrUBufferSize :: Int
- mapDrawcall :: (s -> s') -> Drawcall s' -> Drawcall s
- type Binding = Int
- data RenderIOState s = RenderIOState {
- uniformNameToRenderIO :: IntMap UniformId (s -> Binding -> IO ())
- samplerNameToRenderIO :: IntMap SamplerId (s -> Binding -> IO Int)
- rasterizationNameToRenderIO :: IntMap Int (s -> IO ())
- transformFeedbackToRenderIO :: IntMap Int (s -> GLuint -> IO ())
- inputArrayToRenderIO :: IntMap Int (s -> [([Binding], GLuint, Int) -> ((IO [VAOKey], IO ()), IO ())])
- newRenderIOState :: RenderIOState s
- mapRenderIOState :: (s -> s') -> RenderIOState s' -> RenderIOState s -> RenderIOState s
- compileDrawcalls :: (Monad m, MonadIO m, MonadException m, ContextHandler ctx) => [IO (Drawcall s)] -> RenderIOState s -> ContextT ctx os m (CompiledShader os s)
- data CompileInput s = CompileInput {}
- mkCompInput :: (Drawcall s, [UniformId], [SamplerId], [UniformId], [SamplerId]) -> CompileInput s
- data GpuLimits = GpuLimits {}
- getLimits :: IO GpuLimits
- safeGenerateDrawcalls :: [IO (Drawcall s)] -> IO ([CompileInput s], [String])
- innerCompile :: RenderIOState s -> CompileInput s -> IO (Either String ((IORef GLuint, IO ()), CompiledShader os s))
- createRenderer :: RenderIOState s -> CompileInput s -> GLuint -> Int -> IO ((IORef GLuint, IO ()), CompiledShader os s)
- createDrawRenderer :: RenderIOState s -> CompileInput s -> IORef GLuint -> Int -> IntMap UniformId (s -> Binding -> IO b) -> GLuint -> Int -> CompiledShader os s
- createFeedbackRenderer :: RenderIOState s -> CompileInput s -> GLuint -> (s -> IO (GLuint, GLuint, GLuint, GLuint)) -> Int -> IO ((IORef GLuint, IO ()), CompiledShader os s)
- compileOpenGlShader :: GLuint -> Text -> IO (Maybe String)
- linkProgram :: GLuint -> IO (Maybe String)
- createUniformBuffer :: Integral a => a -> IO GLuint
- addPrimitiveStreamUniform :: Word32 -> Int -> IntMap UniformId (s -> Binding -> IO ()) -> IntMap UniformId (s -> Binding -> IO ())
- bind :: Integral a => IntMap a (s -> Binding -> IO x) -> [(a, a)] -> s -> (x -> IO Bool) -> IO Bool
- orderedUnion :: Ord a => [a] -> [a] -> [a]
- oldAllocateWhichGiveStrangeResults :: Int -> [[Int]] -> [[Int]]
- allocateConsecutiveIndexes :: Integral a => a -> [[a]] -> [[a]]
- getFboError :: MonadIO m => m (Maybe String)
- whenJust' :: (Monad m, Monoid b) => Maybe a -> (a -> m b) -> m b
Documentation
type CompiledShader os s = s -> Render os () Source #
A compiled shader is just a function that takes an environment and returns
a Render
action It could have been called CompiledDrawcall
or Renderer
because it is the same thing.
Drawcall | |
|
mapDrawcall :: (s -> s') -> Drawcall s' -> Drawcall s Source #
data RenderIOState s Source #
RenderIOState | |
|
mapRenderIOState :: (s -> s') -> RenderIOState s' -> RenderIOState s -> RenderIOState s Source #
compileDrawcalls :: (Monad m, MonadIO m, MonadException m, ContextHandler ctx) => [IO (Drawcall s)] -> RenderIOState s -> ContextT ctx os m (CompiledShader os s) Source #
May throw a GPipeException
The multiple drawcalls to be compiled are intended to use the same environment s
(and only one is selected dynamically when rendering).
public
data CompileInput s Source #
mkCompInput :: (Drawcall s, [UniformId], [SamplerId], [UniformId], [SamplerId]) -> CompileInput s Source #
GpuLimits | |
|
safeGenerateDrawcalls :: [IO (Drawcall s)] -> IO ([CompileInput s], [String]) Source #
innerCompile :: RenderIOState s -> CompileInput s -> IO (Either String ((IORef GLuint, IO ()), CompiledShader os s)) Source #
createRenderer :: RenderIOState s -> CompileInput s -> GLuint -> Int -> IO ((IORef GLuint, IO ()), CompiledShader os s) Source #
createDrawRenderer :: RenderIOState s -> CompileInput s -> IORef GLuint -> Int -> IntMap UniformId (s -> Binding -> IO b) -> GLuint -> Int -> CompiledShader os s Source #
createFeedbackRenderer :: RenderIOState s -> CompileInput s -> GLuint -> (s -> IO (GLuint, GLuint, GLuint, GLuint)) -> Int -> IO ((IORef GLuint, IO ()), CompiledShader os s) Source #
addPrimitiveStreamUniform :: Word32 -> Int -> IntMap UniformId (s -> Binding -> IO ()) -> IntMap UniformId (s -> Binding -> IO ()) Source #
bind :: Integral a => IntMap a (s -> Binding -> IO x) -> [(a, a)] -> s -> (x -> IO Bool) -> IO Bool Source #
orderedUnion :: Ord a => [a] -> [a] -> [a] Source #
allocateConsecutiveIndexes :: Integral a => a -> [[a]] -> [[a]] Source #