Plot-ho-matic-0.10.0.0: 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 newHistoryChannel to create a time series plot. The newHistoryChannel function will return an action which is used to send new data to the plotter.

For example:

{-# LANGUAGE DeriveGeneric #-}

import GHC.Generics ( Generic )

import Accessors ( Lookup )
import Control.Concurrent ( forkIO )
import PlotHo

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

messageSender :: (Foo -> Bool -> IO ()) -> IO ()
messageSender newMessage = go True
  where
    go firstMessage = do
      CC.threadDelay 100000
      foo <- receiveFooFromNetworkOrSomething :: IO Foo
      let reset = firstMessage -- reset on the first message
      newMessage foo reset
      go False

main :: IO ()
main = do
  (channel, newMessage) <- addHistoryChannel "it's foo" XAxisCount
  _ <- forkIO (messageSender newMessage)
  runPlotter Nothing [channel]

When main is run, a new channel is created which returns the "new message" action. messageSender is then forked and periodically sends new messages to the plotter. The plotter is then started with runPlotter.

Dynamic data

(Placeholder)

runPlotter :: Maybe PlotterOptions -> [Channel] -> IO () Source #

fire up the the GUI

data PlotterOptions Source #

Some options

Constructors

PlotterOptions 

Fields

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)

newHistoryChannel Source #

Arguments

:: Lookup a 
=> String

channel name

-> XAxisType

what to use for the X axis

-> IO (Channel, a -> Bool -> IO ())

return a channel and a "new message" action which can also reset the history

Simplified time-series channel which automatically generates the signal tree based on Lookup. You have to recompile the plotter if the types change. The plotter will plot a time series of messages put by the action returned by this function. 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. If this is too restrictive, use the more generic newChannel and use a Tree-like type to represent your data, or use newHistoryChannel'.

newHistoryChannel' Source #

Arguments

:: String

channel name

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

History channel which supports data whose structure can change. It does NOT automatically generate the signal tree like newHistoryChannel does. This returns a channel and an action which takes x-axis value, a vector of y axis values, and a tree which indexes these y axis values. If the data structure changes, a new tree should be sent, otherwise there could be indexing errors.

newChannel 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 -> SignalTree a)

how to build the signal tree

-> IO (Channel, a -> IO ())

Return a channel and a "new message" function. You should for a thread which receives messages and calls this action.

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 signal tree.

For examples of this, see the implementation of addHistoryChannel and addHistoryChannel'.

re-exported for convenience

def :: Default a => a #

The default value for this type.

class Lookup a #

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