Skip to content

Instantly share code, notes, and snippets.

@JackTheEngineer
Created September 25, 2018 10:24
Show Gist options
  • Save JackTheEngineer/5ce9f2b5b46989c1a3920569e713c897 to your computer and use it in GitHub Desktop.
Save JackTheEngineer/5ce9f2b5b46989c1a3920569e713c897 to your computer and use it in GitHub Desktop.
module Main where
import Graphics.Rendering.Chart.Easy
import Graphics.Rendering.Chart.Gtk
import qualified Graphics.UI.Gtk as G
import qualified Graphics.Rendering.Cairo as C
import qualified Graphics.UI.Gtk.Gdk.Events as GE
import Graphics.Rendering.Chart.Renderable
import Graphics.Rendering.Chart.Geometry
import Graphics.Rendering.Chart.Drawing
import Graphics.Rendering.Chart.Backend.Cairo
import Data.IORef
import Control.Monad(when)
import System.IO.Unsafe(unsafePerformIO)
-- Yuck. But we really want the convenience function
-- renderableToWindow as to be callable without requiring
-- initGUI to be called first. But newer versions of
-- gtk insist that initGUI is only called once
guiInitVar :: IORef Bool
{-# NOINLINE guiInitVar #-}
guiInitVar = unsafePerformIO (newIORef False)
initGuiOnce :: IO ()
initGuiOnce = do
v <- readIORef guiInitVar
when (not v) $ do
-- G.initGUI
G.unsafeInitGUIForThreadedRTS
writeIORef guiInitVar True
linechart list = toRenderable layout
where
lineplot = plot_lines_values .~ list
$ plot_lines_style . line_color .~ opaque blue
$ plot_lines_title .~ "Plot"
$ def
layout = layout_title .~ "Amplitude Modulation"
$ layout_plots .~ [toPlot lineplot]
$ def
func :: Double -> Double
func x = (sin (x*3.14159/45) + 1) / 2 * (sin (x*3.14159/5))
createWindowAndCanvas :: Renderable a -> Int -> Int -> IO (G.Window, G.DrawingArea)
createWindowAndCanvas chart windowWidth windowHeight = do
window <- G.windowNew
canvas <- G.drawingAreaNew
G.widgetSetSizeRequest window windowWidth windowHeight
G.onExpose canvas $ const (updateCanvas chart canvas)
G.set window [G.containerChild G.:= canvas]
return (window, canvas)
getSerialDataAndUpdateCanvas :: G.DrawingArea ->IO(Bool)
getSerialDataAndUpdateCanvas canvas = do
-- I Thought that here, i could do the fetching of the data from
-- the UART/Serialport and then give the data to "x"
umpdateCanvas (linechart [[ (x, func x) | x <- [0,0.5 .. 40.0 ]]]) canvas
return True
umpdateCanvas :: Renderable a -> G.DrawingArea -> IO Bool
umpdateCanvas chart canvas = do
win <- G.widgetGetDrawWindow canvas
(width, height) <- G.widgetGetSize canvas
regio <- G.regionRectangle $ GE.Rectangle 0 0 width height
let sz = (fromIntegral width, fromIntegral height)
G.drawWindowBeginPaintRegion win regio
G.renderWithDrawable win $ runBackend (defaultEnv bitmapAlignmentFns) (render chart sz)
G.drawWindowEndPaint win
return True
main :: IO ()
main = do
let emptyList = [[]] :: [[(Double, Double)]]
emptyChart = linechart emptyList
initGuiOnce
(window, canvas) <- createWindowAndCanvas emptyChart 400 400
G.set window [G.containerChild G.:= canvas]
window `G.on` G.keyPressEvent $ do
C.liftIO (G.widgetDestroy window)
return True
window `G.on` G.objectDestroy $ G.mainQuit
-- Calls function with the timeout in ms
G.timeoutAdd (getSerialDataAndUpdateCanvas canvas) 20
G.widgetShowAll window
G.mainGUI
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment