| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Graphics.GL.Low.Shader
Contents
- newProgram :: String -> String -> IO Program
- newProgramSafe :: String -> String -> IO (Either ProgramError Program)
- useProgram :: Program -> IO ()
- deleteProgram :: Program -> IO ()
- setUniform1f :: String -> [Float] -> IO ()
- setUniform2f :: String -> [V2 Float] -> IO ()
- setUniform3f :: String -> [V3 Float] -> IO ()
- setUniform4f :: String -> [V4 Float] -> IO ()
- setUniform1i :: String -> [Int] -> IO ()
- setUniform2i :: String -> [V2 Int] -> IO ()
- setUniform3i :: String -> [V3 Int] -> IO ()
- setUniform4i :: String -> [V4 Int] -> IO ()
- setUniform44 :: String -> [M44 Float] -> IO ()
- setUniform33 :: String -> [M33 Float] -> IO ()
- setUniform22 :: String -> [M22 Float] -> IO ()
- data Program
- data ProgramError
- = VertexShaderError String
- | FragmentShaderError String
- | LinkError String
Documentation
A shader program is composed of two cooperating parts: the vertex program and the fragment program. The vertex program is executed once for each vertex. The fragment program is executed once for each pixel covered by a rasterized primitive.
The inputs to the vertex program are:
- a vertex (see Graphics.GL.Low.VAO)
- uniforms
The outputs of the vertex program are:
- clip space position of the vertex, gl_Position
- any number of variables matching inputs to the fragment program
- (if rendering a point, you can also set gl_PointSize)
The inputs to the fragment program are:
- interpolated outputs of the vertex program
- the window position of the pixel, gl_FragCoord
- samplers (see Graphics.GL.Low.Texture)
- uniforms
- gl_FrontFacing, true if pixel is part of a front facing triangle
- (if rendering a point, then you can use gl_PointCoord)
The outputs of the fragment program are:
- the depth of the pixel, gl_FragDepth, which will default to the pixel's Z.
- color of the pixel.
Arguments
| :: String | vertex shader source code |
| -> String | fragment shader source code |
| -> IO Program |
Compile the code for a vertex shader and a fragment shader, then link them into a new program. If the compiler or linker fails it will throw a ProgramError.
newProgramSafe :: String -> String -> IO (Either ProgramError Program) Source
Same as newProgram but does not throw exceptions.
useProgram :: Program -> IO () Source
Install a program into the rendering pipeline. Replaces the program already in use, if any.
deleteProgram :: Program -> IO () Source
Delete a program.
setUniform1f :: String -> [Float] -> IO () Source
setUniform2f :: String -> [V2 Float] -> IO () Source
setUniform3f :: String -> [V3 Float] -> IO () Source
setUniform4f :: String -> [V4 Float] -> IO () Source
setUniform1i :: String -> [Int] -> IO () Source
setUniform2i :: String -> [V2 Int] -> IO () Source
setUniform3i :: String -> [V3 Int] -> IO () Source
setUniform4i :: String -> [V4 Int] -> IO () Source
setUniform44 :: String -> [M44 Float] -> IO () Source
setUniform33 :: String -> [M33 Float] -> IO () Source
setUniform22 :: String -> [M22 Float] -> IO () Source
data ProgramError Source
The error message emitted by the driver when shader compilation or linkage fails.
Constructors
| VertexShaderError String | |
| FragmentShaderError String | |
| LinkError String |
Instances
Example

This example renders three differently-shaded triangles. The window coordinates, the interpolated location on the triangle, and the elapsed time are used to color the triangles respectively.
module Main where
import Control.Monad.Loops (whileM_)
import qualified Data.Vector.Storable as V
import Data.Maybe (fromJust)
import qualified Graphics.UI.GLFW as GLFW
import Linear
import Graphics.GL.Low
main = do
GLFW.init
GLFW.windowHint (GLFW.WindowHint'ContextVersionMajor 3)
GLFW.windowHint (GLFW.WindowHint'ContextVersionMinor 2)
GLFW.windowHint (GLFW.WindowHint'OpenGLForwardCompat True)
GLFW.windowHint (GLFW.WindowHint'OpenGLProfile GLFW.OpenGLProfile'Core)
mwin <- GLFW.createWindow 640 480 "Shaders" Nothing Nothing
case mwin of
Nothing -> putStrLn "createWindow failed"
Just win -> do
GLFW.makeContextCurrent (Just win)
GLFW.swapInterval 1
(vao, prog1, prog2, prog3) <- setup
whileM_ (not <$> GLFW.windowShouldClose win) $ do
GLFW.pollEvents
t <- (realToFrac . fromJust) <$> GLFW.getTime
draw vao prog1 prog2 prog3 t
GLFW.swapBuffers win
setup = do
vao <- newVAO
bindVAO vao
vsource <- readFile "shader.vert"
fsource1 <- readFile "shader1.frag"
fsource2 <- readFile "shader2.frag"
fsource3 <- readFile "shader3.frag"
prog1 <- newProgram vsource fsource1
prog2 <- newProgram vsource fsource2
prog3 <- newProgram vsource fsource3
useProgram prog1
let blob = V.fromList
[ -0.4, -0.4, 0, 0
, 0, 0.4, 0, 1
, 0.4, -0.4, 1, 1] :: V.Vector Float
vbo <- newBufferObject blob StaticDraw
bindVBO vbo
setVertexLayout
[ Attrib "position" 2 GLFloat
, Attrib "location" 2 GLFloat ]
return (vao, prog1, prog2, prog3)
draw vao prog1 prog2 prog3 t = do
clearColorBuffer (0,0,0)
bindVAO vao
drawThing prog1 t (V3 (-0.5) 0.5 0.0)
drawThing prog2 t (V3 0.5 0.5 0.0)
drawThing prog3 t (V3 0.0 (-0.5) (-0.0))
drawThing :: Program -> Float -> V3 Float -> IO ()
drawThing prog t shift = do
let angle = t / 5
let move = mkTransformation (axisAngle (V3 0 0 1) angle) shift
useProgram prog
setUniform1f "time" [t]
setUniform44 "move" [transpose move]
drawTriangles 3
Where the vertex shader is
#version 150
uniform mat4 move;
in vec2 position;
in vec2 location;
out vec2 Location;
void main()
{
gl_Position = move * vec4(position, 0.0, 1.0);
Location = location;
}
And the three fragment shaders are
#version 150
uniform float time;
in vec2 Location;
out vec4 outColor;
void main()
{
float x = gl_FragCoord.x / 640;
float y = gl_FragCoord.y / 480;
outColor = vec4(
fract(x*25) < 0.5 ? 1.0 : 0.0,
fract(y*25) < 0.5 ? 1.0 : 0.0,
0.0, 1.0
);
}
#version 150
uniform float time;
in vec2 Location;
out vec4 outColor;
void main()
{
outColor = vec4(
fract(Location.x*10) < 0.5 ? 1.0 : 0.0,
fract(Location.y*10) < 0.5 ? 1.0 : 0.0,
0.0, 1.0
);
}
#version 150
uniform float time;
in vec2 Location;
out vec4 outColor;
void main()
{
float t = time;
outColor = vec4(
fract(Location.x*5) < 0.5 ? sin(t*3.145) : cos(t*4.567),
fract(Location.y*5) < 0.5 ? cos(t*6.534) : sin(t*4.321),
0.0, 1.0
);
}