| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Graphics.Rendering.Ombra.Object
Contents
- data Object gs is where
- nothing :: Object '[] '[]
- geom :: Geometry (i ': is) -> Object '[] (i ': is)
- modifyGeometry :: (Geometry (i ': is) -> Geometry (i' ': is')) -> Object gs (i ': is) -> Object gs (i' ': is')
- depthTest :: Bool -> Object gs is -> Object gs is
- depthMask :: Bool -> Object gs is -> Object gs is
- colorMask :: (Bool, Bool, Bool, Bool) -> Object gs is -> Object gs is
- type ShaderVars = Set ShaderVar
- type VOShaderVars o = (ShaderVars o, ShaderVars (VertexShaderOutput ': o))
- blend :: Mode -> Object gs is -> Object gs is
- noBlend :: Object gs is -> Object gs is
- transparency :: Mode
- additive :: Mode
- stencil :: Mode -> Object gs is -> Object gs is
- noStencil :: Object gs is -> Object gs is
- data CullFace
- cull :: CullFace -> Object gs is -> Object gs is
- noCull :: Object gs is -> Object gs is
- data Global g
- (-=) :: (ShaderVar g, Uniform S g) => (a -> g) -> CPU S g -> Global g
- withTexture :: Texture -> (ActiveTexture -> Global g) -> Global g
- withTexSize :: Texture -> ((Int, Int) -> Global g) -> Global g
- withFramebufferSize :: ((Int, Int) -> Global g) -> Global g
- data ActiveTexture
- mirror :: (ShaderVar g, Uniform M g) => Proxy g -> CPU M g -> Global g
- type family CPUMirror g
- class MemberGlobal g gs where
- class RemoveGlobal g gs' where
Creating and modifying objects
data Object gs is where Source #
A geometry associated with some uniforms.
Constructors
| (:~>) :: Global g -> Object gs is -> Object (g ': gs) is infixr 2 | Add a Global to an Object. |
Instances
| (ShaderVars gs, ShaderVars is) => Monoid (Object gs is) Source # | |
modifyGeometry :: (Geometry (i ': is) -> Geometry (i' ': is')) -> Object gs (i ': is) -> Object gs (i' ': is') Source #
Modify the geometry of an Object.
Object properties
depthTest :: Bool -> Object gs is -> Object gs is Source #
Enable/disable depth testing for a Object.
depthMask :: Bool -> Object gs is -> Object gs is Source #
Enable/disable writing into the depth buffer for a Object.
colorMask :: (Bool, Bool, Bool, Bool) -> Object gs is -> Object gs is Source #
Enable/disable writing into the four channels of the color buffer for a
Object.
type ShaderVars = Set ShaderVar Source #
A type-level set of ShaderVars.
type VOShaderVars o = (ShaderVars o, ShaderVars (VertexShaderOutput ': o)) Source #
ShaderVars for the output of VartexShader.
Blending
blend :: Mode -> Object gs is -> Object gs is Source #
Enable blending and set the blending mode for an Object.
transparency :: Mode Source #
Standard transparency (default).
Stencil test
stencil :: Mode -> Object gs is -> Object gs is Source #
Enable stencil testing and set the stencil mode for an Object.
Culling
Globals
(-=) :: (ShaderVar g, Uniform S g) => (a -> g) -> CPU S g -> Global g infixr 4 Source #
Create a Global from a pure value. The first argument is ignored,
it just provides the type (you can use the constructor of the GPU type).
You can use this to set the value of a shader uniform.
withTexture :: Texture -> (ActiveTexture -> Global g) -> Global g Source #
Create a Global activating a Texture. Note that the corresponding CPU
type of Sampler2D is ActiveTexture, not Texture.
withFramebufferSize :: ((Int, Int) -> Global g) -> Global g Source #
Create a Global using the size of the framebuffer.
data ActiveTexture Source #
A Texture ready to be passed as an uniform.
Mirror globals
mirror :: (ShaderVar g, Uniform M g) => Proxy g -> CPU M g -> Global g Source #
Like -= but for mirror types.
type family CPUMirror g Source #
The mirror type of a certain global.
For instance:
data T = T GVec3 Float -- In the shader module
data T = T Vec3 Float -- CPU version of the uniform type
type CPUMirror GPU.T = T
Modifying globals
class MemberGlobal g gs where Source #
Minimal complete definition
Methods
(~~>) :: Uniform S g => (CPU S g -> Global g) -> Object gs is -> Object gs is infixr 2 Source #
Modify the global of an Object. This doesn't work with mirror
globals.
Instances
| ((~) Bool ((==) * g g1) False, MemberGlobal g gs) => MemberGlobal g ((:) * g1 gs) Source # | |
| MemberGlobal g ((:) * g gs) Source # | |
class RemoveGlobal g gs' where Source #
Minimal complete definition
Methods
(*~>) :: (a -> g) -> Object gs' is -> Object (Remove g gs') is infixr 2 Source #
Remove a global from an Object.
Instances
| ((~) [*] (Remove g ((:) * g' gs')) ((:) * g' (Remove g gs')), RemoveGlobal g gs') => RemoveGlobal g ((:) * g' gs') Source # | |
| (~) [*] (Remove g ((:) * g gs')) gs' => RemoveGlobal g ((:) * g gs') Source # | |