{-# LANGUAGE ScopedTypeVariables #-}
module Graphics.DynamicGraph.FillLine (
renderFilledLine,
module Graphics.DynamicGraph.ColorMaps
) where
import Graphics.Rendering.OpenGL
import Graphics.GLUtil
import Foreign.Storable
import Foreign.Marshal.Array
import Pipes
import Graphics.DynamicGraph.ColorMaps
import Paths_dynamic_graph
renderFilledLine :: IsPixelData a
=> Int
-> [GLfloat]
-> IO (a -> IO ())
renderFilledLine samples colorMap = do
vertFN <- getDataFileName "shaders/fill_line.vert"
fragFN <- getDataFileName "shaders/fill_line.frag"
vs <- loadShader VertexShader vertFN
fs <- loadShader FragmentShader fragFN
p <- linkShaderProgram [vs, fs]
currentProgram $= Just p
ab <- genObjectName
locc <- get $ attribLocation p "coord"
let stride = fromIntegral $ sizeOf (undefined::GLfloat) * 2
vad = VertexArrayDescriptor 2 Float stride offset0
bindBuffer ArrayBuffer $= Just ab
vertexAttribArray locc $= Enabled
vertexAttribPointer locc $= (ToFloat, vad)
let xCoords :: [GLfloat]
xCoords = [-1, -1, 1, -1, 1, 1, -1, 1]
withArray xCoords $ \ptr ->
bufferData ArrayBuffer $= (fromIntegral $ sizeOf(undefined::GLfloat) * 8, ptr, StaticDraw)
let yCoords :: [GLfloat]
yCoords = replicate samples 0
activeTexture $= TextureUnit 0
texture Texture2D $= Enabled
to <- loadTexture (TexInfo (fromIntegral samples) 1 TexMono yCoords)
loc <- get $ uniformLocation p "texture"
asUniform (0 :: GLint) loc
textureFilter Texture2D $= ((Linear', Nothing), Linear')
textureWrapMode Texture2D S $= (Repeated, ClampToEdge)
textureWrapMode Texture2D T $= (Repeated, Repeat)
activeTexture $= TextureUnit 1
texture Texture2D $= Enabled
loadTexture (TexInfo (fromIntegral $ length colorMap `quot` 3) 1 TexRGB colorMap)
textureFilter Texture2D $= ((Linear', Nothing), Linear')
textureWrapMode Texture2D S $= (Repeated, ClampToEdge)
textureWrapMode Texture2D T $= (Repeated, ClampToEdge)
loc <- get $ uniformLocation p "colorMap"
asUniform (1 :: GLint) loc
let lcm :: GLfloat
lcm = fromIntegral $ length colorMap `quot` 3
loc <- get $ uniformLocation p "scale"
asUniform ((lcm - 1) / lcm) loc
loc <- get $ uniformLocation p "offset"
asUniform (0.5 / lcm) loc
activeTexture $= TextureUnit 0
return $ \vbd -> do
currentProgram $= Just p
reloadTexture to (TexInfo (fromIntegral samples) 1 TexMono vbd)
bindBuffer ArrayBuffer $= Just ab
vertexAttribArray locc $= Enabled
vertexAttribPointer locc $= (ToFloat, vad)
drawArrays Quads 0 4