mirror of
				https://github.com/Drezil/dear-implot.hs.git
				synced 2025-11-03 22:51:06 +01:00 
			
		
		
		
	Add demo
This commit is contained in:
		
							
								
								
									
										1
									
								
								.gitignore
									
									
									
									
										vendored
									
									
										Normal file
									
								
							
							
						
						
									
										1
									
								
								.gitignore
									
									
									
									
										vendored
									
									
										Normal file
									
								
							@@ -0,0 +1 @@
 | 
			
		||||
/imgui.ini
 | 
			
		||||
							
								
								
									
										45
									
								
								Main.hs
									
									
									
									
									
								
							
							
						
						
									
										45
									
								
								Main.hs
									
									
									
									
									
								
							@@ -1,18 +1,28 @@
 | 
			
		||||
{-# LANGUAGE BlockArguments #-}
 | 
			
		||||
{-# LANGUAGE LambdaCase #-}
 | 
			
		||||
{-# LANGUAGE OverloadedStrings #-}
 | 
			
		||||
{-# LANGUAGE RankNTypes #-}
 | 
			
		||||
 | 
			
		||||
module Main (main) where
 | 
			
		||||
 | 
			
		||||
import Control.Exception
 | 
			
		||||
import Control.Monad.IO.Class
 | 
			
		||||
import Control.Monad.Managed
 | 
			
		||||
import Data.Binary.Get (getInt16le, isEmpty, runGet)
 | 
			
		||||
import qualified Data.ByteString as BS
 | 
			
		||||
import Data.ByteString.Lazy (fromStrict)
 | 
			
		||||
import Data.List (iterate')
 | 
			
		||||
import DearImGui
 | 
			
		||||
import DearImGui.OpenGL2
 | 
			
		||||
import qualified DearImGui.Plot as ImPlot
 | 
			
		||||
import DearImGui.SDL
 | 
			
		||||
import DearImGui.SDL.OpenGL
 | 
			
		||||
import GHC.Float (int2Float)
 | 
			
		||||
import GHC.Int (Int16)
 | 
			
		||||
import Graphics.GL
 | 
			
		||||
import Pipes
 | 
			
		||||
import Pipes.PulseSimple
 | 
			
		||||
import Pipes.Safe (runSafeT)
 | 
			
		||||
import SDL
 | 
			
		||||
 | 
			
		||||
main :: IO ()
 | 
			
		||||
@@ -42,21 +52,43 @@ main = do
 | 
			
		||||
    -- Initialize ImGui's OpenGL backend
 | 
			
		||||
    _ <- managed_ $ bracket_ openGL2Init openGL2Shutdown
 | 
			
		||||
 | 
			
		||||
    liftIO $ mainLoop win
 | 
			
		||||
    liftIO $ runSafeT (runEffect (readPulse "dear-pulse" Nothing 25 >-> mainLoop win))
 | 
			
		||||
 | 
			
		||||
mainLoop :: Window -> IO ()
 | 
			
		||||
-- | Binary decoder
 | 
			
		||||
decodeSampleList :: BS.ByteString -> [Int16]
 | 
			
		||||
decodeSampleList = runGet get . fromStrict
 | 
			
		||||
  where
 | 
			
		||||
    get = do
 | 
			
		||||
      empty <- isEmpty
 | 
			
		||||
      if empty
 | 
			
		||||
        then return []
 | 
			
		||||
        else do
 | 
			
		||||
          sample <- getInt16le
 | 
			
		||||
          rest <- get
 | 
			
		||||
          return (sample : rest)
 | 
			
		||||
 | 
			
		||||
mainLoop :: MonadIO m => Window -> Consumer' BS.ByteString m ()
 | 
			
		||||
mainLoop win = do
 | 
			
		||||
  -- Process the event loop
 | 
			
		||||
  untilNothingM pollEventWithImGui
 | 
			
		||||
 | 
			
		||||
  -- Get audio buffer
 | 
			
		||||
  buf <- await
 | 
			
		||||
  let maxInt16 :: Int16
 | 
			
		||||
      maxInt16 = maxBound
 | 
			
		||||
      maxInt16f = int2Float $ fromIntegral maxInt16
 | 
			
		||||
      samples :: [Float]
 | 
			
		||||
      samples = map (\x' -> int2Float (fromIntegral x') / maxInt16f) $ decodeSampleList buf
 | 
			
		||||
 | 
			
		||||
  -- Tell ImGui we're starting a new frame
 | 
			
		||||
  openGL2NewFrame
 | 
			
		||||
  sdl2NewFrame win
 | 
			
		||||
  newFrame
 | 
			
		||||
 | 
			
		||||
  -- Build the GUI
 | 
			
		||||
  bracket_ (ImPlot.beginPlot "Hello, ImPlot!") ImPlot.endPlot do
 | 
			
		||||
    ImPlot.plotLine "test" [0.0, 0.1, 0.2, 0.3, 0.4] [0.1, 0.2, 0.3, 0.1, 0.5]
 | 
			
		||||
  ImPlot.setNextPlotLimits (0, 1) (-1, 1)
 | 
			
		||||
  liftIO $ bracket_ (ImPlot.beginPlot "Audio") ImPlot.endPlot do
 | 
			
		||||
    ImPlot.plotLine "pulse-input" xs samples
 | 
			
		||||
 | 
			
		||||
  -- Render
 | 
			
		||||
  glClear GL_COLOR_BUFFER_BIT
 | 
			
		||||
@@ -69,3 +101,8 @@ mainLoop win = do
 | 
			
		||||
  mainLoop win
 | 
			
		||||
  where
 | 
			
		||||
    untilNothingM m = m >>= maybe (return ()) (\_ -> untilNothingM m)
 | 
			
		||||
    xs = range
 | 
			
		||||
    range :: [Float]
 | 
			
		||||
    range = take 1764 $ iterate' (+ step) 0.0
 | 
			
		||||
    step :: Float
 | 
			
		||||
    step = 1 / 1764
 | 
			
		||||
 
 | 
			
		||||
							
								
								
									
										22
									
								
								README.md
									
									
									
									
									
								
							
							
						
						
									
										22
									
								
								README.md
									
									
									
									
									
								
							@@ -1,2 +1,24 @@
 | 
			
		||||
# implot binding
 | 
			
		||||
 | 
			
		||||
This project contains Haskell bindings to the
 | 
			
		||||
[dear-imgui](https://github.com/ocornut/imgui)
 | 
			
		||||
[implot](https://github.com/epezent/implot) project.
 | 
			
		||||
 | 
			
		||||
The [demo](./Main.hs) shows a LinePlot of a pulseaudio input:
 | 
			
		||||
 | 
			
		||||

 | 
			
		||||
 | 
			
		||||
## Contribute
 | 
			
		||||
 | 
			
		||||
To build the project and the demo, make sure these projects are cloned:
 | 
			
		||||
 | 
			
		||||
- ./github.com/haskell-game/dear-imgui.hs/
 | 
			
		||||
- ./github.com/TristanCacqueray/pipes-pulse-simple/
 | 
			
		||||
- ./github.com/TristanCacqueray/dear-implot.hs/
 | 
			
		||||
 | 
			
		||||
Then run:
 | 
			
		||||
 | 
			
		||||
```ShellSession
 | 
			
		||||
$ cabal build
 | 
			
		||||
$ cabal run test
 | 
			
		||||
```
 | 
			
		||||
 
 | 
			
		||||
@@ -1,2 +1,2 @@
 | 
			
		||||
packages: . ../../haskell-game/dear-imgui.hs/
 | 
			
		||||
packages: . ../../haskell-game/dear-imgui.hs/ ../pipes-pulse-simple/
 | 
			
		||||
flags: +sdl +opengl2 -vulkan
 | 
			
		||||
 
 | 
			
		||||
@@ -22,17 +22,26 @@ library
 | 
			
		||||
  include-dirs:
 | 
			
		||||
    implot
 | 
			
		||||
    imgui
 | 
			
		||||
  build-depends:
 | 
			
		||||
      base
 | 
			
		||||
  build-depends: base
 | 
			
		||||
               , StateVar
 | 
			
		||||
               , containers
 | 
			
		||||
    , managed
 | 
			
		||||
               , dear-imgui
 | 
			
		||||
               , inline-c
 | 
			
		||||
               , inline-c-cpp
 | 
			
		||||
    , StateVar
 | 
			
		||||
    , dear-imgui
 | 
			
		||||
               , managed
 | 
			
		||||
 | 
			
		||||
executable test
 | 
			
		||||
  main-is: Main.hs
 | 
			
		||||
  default-language: Haskell2010
 | 
			
		||||
  build-depends: base, sdl2, gl, dear-imgui, dear-implot, managed
 | 
			
		||||
  build-depends: base
 | 
			
		||||
               , binary
 | 
			
		||||
               , bytestring
 | 
			
		||||
               , dear-imgui
 | 
			
		||||
               , dear-implot
 | 
			
		||||
               , gl
 | 
			
		||||
               , managed
 | 
			
		||||
               , pipes
 | 
			
		||||
               , pipes-safe
 | 
			
		||||
               , sdl2
 | 
			
		||||
               , pipes-pulse-simple
 | 
			
		||||
  ghc-options: -Wall
 | 
			
		||||
 
 | 
			
		||||
		Reference in New Issue
	
	Block a user