Plot-ho-matic-0.9.0.10: Real-time line plotter for generic data

Safe HaskellNone
LanguageHaskell2010

PlotHo

Contents

Synopsis

Usage

The easiest way to use this library is to use Generic to derive an instance of Lookup for your data type, and then use addHistoryChannel to create a time series. You need to pass addHistoryChannel an action which periodically sends a new message.

For example:

{-# LANGUAGE DeriveGeneric #-}

import GHC.Generics ( Generic )
import Accessors ( Lookup )
import PlotHo

data Foo =
  = Foo
    { value1 :: Double
    , value2 :: Double
    } deriving Generic
instance Lookup Foo

messageSender :: (Foo -> True -> IO ()) -> IO ()
messageSender newMessage = forever $ do
  CC.threadDelay 100000
  foo <- receiveFooFromNetworkOrSomething :: IO Foo
  let reset = False -- never reset in this example
  newMessage foo reset

main :: IO ()
main = runPlotter $
  addHistoryChannel "it's foo" XAxisCount messageSender

When the plotter executes, messageSender will be forked and will forever listen for new messages. Every time it receives a new message it will call the newMessage action which instructs the plotter to add a data point and redraw.

Dynamic data

(Placeholder)

data Plotter a Source #

add channels to this, then run it with runPlotter

Instances

Monad Plotter Source # 

Methods

(>>=) :: Plotter a -> (a -> Plotter b) -> Plotter b #

(>>) :: Plotter a -> Plotter b -> Plotter b #

return :: a -> Plotter a #

fail :: String -> Plotter a #

Functor Plotter Source # 

Methods

fmap :: (a -> b) -> Plotter a -> Plotter b #

(<$) :: a -> Plotter b -> Plotter a #

Applicative Plotter Source # 

Methods

pure :: a -> Plotter a #

(<*>) :: Plotter (a -> b) -> Plotter a -> Plotter b #

(*>) :: Plotter a -> Plotter b -> Plotter b #

(<*) :: Plotter a -> Plotter b -> Plotter a #

MonadIO Plotter Source # 

Methods

liftIO :: IO a -> Plotter a #

runPlotter :: Plotter () -> IO () Source #

fire up the the GUI

data XAxisType Source #

Constructors

XAxisTime

time since the first message

XAxisTime0

time since the first message, normalized to 0 (to reduce plot jitter)

XAxisCount

message index

XAxisCount0

message index, normalized to 0 (to reduce plot jitter)

addHistoryChannel Source #

Arguments

:: Lookup a 
=> String

channel name

-> XAxisType

what to use for the X axis

-> ((a -> Bool -> IO ()) -> IO ())

worker which is passed a "new message" function, this will be forked with forkIO

-> Plotter () 

Simplified time-series channel which passes a "send message" function to a worker and forks it using forkIO. The plotter will plot a time series of messages sent by the worker. The worker should pass True to reset the message history, so sending True the first message and False subsequent messages is a good starting place. You will have to recompile the plotter if the types change. If you don't want to do this, use the more generic addChannel interface and use a type like a Tree to represent your data, or use the addHistoryChannel function.

addHistoryChannel' Source #

Arguments

:: String

channel name

-> ((Double -> Vector Double -> Maybe Meta -> IO ()) -> IO ())

worker which is passed a "new message" function, this will be forked with forkIO

-> Plotter () 

Dynamic time-series channel which can change its signal tree without recompiling the plotter.

addChannel Source #

Arguments

:: String

channel name

-> (a -> a -> Bool)

Is the signal tree the same? This is used for instance if signals have changed and the plotter needs to rebuild the signal tree. This lets you keep the plotter running and change other programs which send messages to the plotter.

-> (a -> [Tree ([String], Either String (a -> [[(Double, Double)]]))])

how to build the signal tree

-> ((a -> IO ()) -> IO ())

worker which is passed a "new message" function, this will be forked with forkIO

-> Plotter () 

This is the general interface to plot whatever you want. Use this when you want to give the whole time series in one go, rather than one at a time such as with addHistoryChannel. Using types or data, you must encode the signal tree with the message so that the plotter can build you the nice message toggle tree.

re-exported for convenience

class Lookup a #

Things which you can make a tree of labeled getters for. You should derive this using GHC.Generics.