GPipe-2.2.5: Typesafe functional GPU graphics programming

Safe HaskellNone
LanguageHaskell98

Graphics.GPipe.Shader

Contents

Description

A Shader is a monad in which PrimitiveStreams and FragmentStreams live, together with samplers and uniform values. Any computations made on the streams and values in the Shader monad will be performed on the GPU. A Shader needs to be compiled before it can be used. In order to make it work over different environments after it has been compiled, it closes over an environment value just like a Reader monad, with the distinction that there is no ask action, since we cannot make the actual monad operation depend on the environment.

A Shader is an instance of Alternative and MonadPlus which makes it possible to express choice with functions like guard. The left most alternative will always be the resulting monad.

Synopsis

The Shader monad

data Shader os s a Source #

The monad in which all GPU computations are done. 'Shader os s a' lives in an object space os and a context with format f, closing over an environent of type s.

Instances
Monad (Shader os s) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Shader

Methods

(>>=) :: Shader os s a -> (a -> Shader os s b) -> Shader os s b #

(>>) :: Shader os s a -> Shader os s b -> Shader os s b #

return :: a -> Shader os s a #

fail :: String -> Shader os s a #

Functor (Shader os s) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Shader

Methods

fmap :: (a -> b) -> Shader os s a -> Shader os s b #

(<$) :: a -> Shader os s b -> Shader os s a #

Applicative (Shader os s) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Shader

Methods

pure :: a -> Shader os s a #

(<*>) :: Shader os s (a -> b) -> Shader os s a -> Shader os s b #

liftA2 :: (a -> b -> c) -> Shader os s a -> Shader os s b -> Shader os s c #

(*>) :: Shader os s a -> Shader os s b -> Shader os s b #

(<*) :: Shader os s a -> Shader os s b -> Shader os s a #

Alternative (Shader os s) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Shader

Methods

empty :: Shader os s a #

(<|>) :: Shader os s a -> Shader os s a -> Shader os s a #

some :: Shader os s a -> Shader os s [a] #

many :: Shader os s a -> Shader os s [a] #

MonadPlus (Shader os s) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Shader

Methods

mzero :: Shader os s a #

mplus :: Shader os s a -> Shader os s a -> Shader os s a #

compileShader :: (ContextHandler ctx, MonadIO m, MonadException m) => Shader os x () -> ContextT ctx os m (CompiledShader os x) Source #

Compiles a shader into a CompiledShader. This action will usually take a second or more, so put it during a loading sequence or something.

May throw a GPipeException if the graphics driver doesn't support something in this shader (e.g. too many interpolated floats sent between a vertex and a fragment shader)

type CompiledShader os s = s -> Render os () Source #

A compiled shader is just a function that takes an environment and returns a Render action

The Render monad

data Render os a Source #

A monad in which shaders are run.

Instances
Monad (Render os) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Context

Methods

(>>=) :: Render os a -> (a -> Render os b) -> Render os b #

(>>) :: Render os a -> Render os b -> Render os b #

return :: a -> Render os a #

fail :: String -> Render os a #

Functor (Render os) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Context

Methods

fmap :: (a -> b) -> Render os a -> Render os b #

(<$) :: a -> Render os b -> Render os a #

Applicative (Render os) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Context

Methods

pure :: a -> Render os a #

(<*>) :: Render os (a -> b) -> Render os a -> Render os b #

liftA2 :: (a -> b -> c) -> Render os a -> Render os b -> Render os c #

(*>) :: Render os a -> Render os b -> Render os b #

(<*) :: Render os a -> Render os b -> Render os a #

render :: (ContextHandler ctx, MonadIO m, MonadException m) => Render os () -> ContextT ctx os m () Source #

Run a Render monad, that may have the effect of windows or textures being drawn to.

May throw a GPipeException if a combination of draw images (FBO) used by this render call is unsupported by the graphics driver

Shader monad combinators

guard' :: (s -> Bool) -> Shader os s () Source #

Like guard, but dependent on the Shaders environment value. Since this will be evaluated at shader run time, as opposed to shader compile time for guard, using this to do recursion will make compileShader diverge. You can break that divergence by combining it with a normal guard and a maximum loop count.

mapShader :: (s -> s') -> Shader os s' a -> Shader os s a Source #

Map the environment to a different environment and run a Shader in that sub environment, returning it's result.

maybeShader :: (s -> Maybe s') -> Shader os s' () -> Shader os s () Source #

Conditionally run the effects of a shader when a Maybe value is Just something.

chooseShader :: (s -> Either s' s'') -> Shader os s' a -> Shader os s'' a -> Shader os s a Source #

Select one of two Shader actions based on whether an Either value is Left or Right.

silenceShader :: Shader os s a -> Shader os s a Source #

Discard all effects of a Shader action (i.e., dont draw anything) and just return the resulting value.