dynamic-graph-0.1.0.13: Draw and update graphs in real time with OpenGL

Safe HaskellNone
LanguageHaskell2010

Graphics.DynamicGraph.Line

Description

Draw and update line graphs with OpenGL.

Based on: https://en.wikibooks.org/wiki/OpenGL_Programming/Scientific_OpenGL_Tutorial_02

Example usage:

import Control.Monad
import Control.Monad.Trans.Except
import Control.Error.Util
import Control.Concurrent
import Control.Applicative
import Pipes
import qualified Pipes.Prelude as P
import System.Random
import Graphics.Rendering.OpenGL

import Graphics.DynamicGraph.Line
import Graphics.DynamicGraph.Window

randomVect :: Producer [GLfloat] IO ()
randomVect =  P.repeatM $ do
    res <- replicateM 1000 randomIO
    threadDelay 10000
    return res

main = exceptT putStrLn return $ do
    res <- lift setupGLFW
    unless res (throwE "Unable to initilize GLFW")

    lineGraph <- window 1024 480 $ pipeify <$> renderLine 1000 1024

    lift $ runEffect $ randomVect >-> lineGraph
Synopsis

Documentation

renderLine Source #

Arguments

:: IsPixelData a 
=> Int

The number of samples in each buffer passed to the rendering function.

-> Int

The number of vertices in the plotted graph.

-> IO (a -> IO ())

The function that does the rendering. Takes an instance of IsPixelData containing the specified number of y values.

Returns a function that renders a line graph into the current OpenGL context.

All OpenGL based initialization of the rendering function (loading of shaders, etc) is performed before the function is returned.

This function must be called with an OpenGL context currently set.