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