dear-imgui.hs/Main.hs

205 lines
5.0 KiB
Haskell
Raw Permalink Normal View History

2021-01-24 15:27:03 +00:00
{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
module Main (main) where
2021-02-06 13:26:28 +00:00
import Control.Monad
2021-01-24 15:56:14 +00:00
import Data.IORef
import qualified Data.Vector as Vector
2021-01-24 15:27:03 +00:00
import DearImGui
2021-02-06 14:44:58 +00:00
import DearImGui.OpenGL3
2021-01-24 18:25:40 +00:00
import DearImGui.SDL
import DearImGui.SDL.OpenGL
2021-01-24 15:27:03 +00:00
import Control.Exception
import Graphics.GL
import SDL
main :: IO ()
main = do
initializeAll
bracket (createWindow "Hello, Dear ImGui!" defaultWindow { windowGraphicsContext = OpenGLContext defaultOpenGL }) destroyWindow \w ->
bracket (glCreateContext w) glDeleteContext \glContext ->
bracket createContext destroyContext \_imguiContext ->
bracket_ (sdl2InitForOpenGL w glContext) sdl2Shutdown $
2021-02-06 14:44:58 +00:00
bracket_ openGL3Init openGL3Shutdown do
2021-01-24 15:27:03 +00:00
checkVersion
styleColorsLight
2021-01-25 09:11:46 +00:00
checked <- newIORef False
color <- newIORef $ ImVec3 1 0 0
slider <- newIORef (0.42, 0, 0.314)
2021-01-28 23:38:59 +00:00
r <- newIORef 4
pos <- newIORef $ ImVec2 64 64
size' <- newIORef $ ImVec2 512 512
selected <- newIORef 4
2021-02-06 13:26:28 +00:00
tab1 <- newIORef True
tab2 <- newIORef True
loop w checked color slider r pos size' selected tab1 tab2
2021-01-24 15:27:03 +00:00
2021-01-28 23:38:59 +00:00
2021-08-30 17:08:23 +00:00
loop
:: Window
-> IORef Bool
-> IORef ImVec3
-> IORef (Float, Float, Float)
-> IORef Int
-> IORef ImVec2
-> IORef ImVec2
2021-08-30 17:08:23 +00:00
-> IORef Int
2021-02-06 13:26:28 +00:00
-> IORef Bool
-> IORef Bool
-> IO ()
2021-08-30 17:08:23 +00:00
loop window checked color slider r pos size' selected tab1Ref tab2Ref = do
shouldQuit <- checkEvents
2021-01-24 15:27:03 +00:00
2021-02-06 14:44:58 +00:00
openGL3NewFrame
2021-08-30 16:57:00 +00:00
sdl2NewFrame
2021-01-24 15:27:03 +00:00
newFrame
-- showDemoWindow
-- showMetricsWindow
-- showAboutWindow
-- showUserGuide
setNextWindowPos pos ImGuiCond_Once Nothing
setNextWindowSize size' ImGuiCond_Once
-- Works, but will make the window contents illegible without doing something more involved.
2021-08-30 17:08:23 +00:00
-- setNextWindowContentSize size'
-- setNextWindowSizeConstraints size' size'
setNextWindowCollapsed False ImGuiCond_Once
setNextWindowBgAlpha 0.42
2021-01-24 15:27:03 +00:00
begin "My Window"
2021-02-06 13:26:28 +00:00
2021-01-24 15:27:03 +00:00
text "Hello!"
2021-02-06 13:26:28 +00:00
beginTabBar "My tab bar" ImGuiTabBarFlags_Reorderable >>= whenTrue do
beginTabItem "Tab 1" tab1Ref ImGuiTabBarFlags_None >>= whenTrue do
text "Tab 1 is currently selected."
endTabItem
beginTabItem "Tab 2" tab2Ref ImGuiTabBarFlags_None >>= whenTrue do
text "Tab 2 is selected now."
endTabItem
reOpen <- tabItemButton "ReopenTabs" ImGuiTabItemFlags_Trailing
when reOpen do
writeIORef tab1Ref True
writeIORef tab2Ref True
endTabBar
2021-01-28 23:38:59 +00:00
listBox "Items" r [ "A", "B", "C" ]
2021-01-24 15:27:03 +00:00
button "Click me" >>= \case
2021-01-24 17:35:00 +00:00
True -> openPopup "Button Popup"
2021-01-24 15:27:03 +00:00
False -> return ()
2021-01-24 17:39:44 +00:00
isItemHovered >>= whenTrue do
beginTooltip
text "Tooltip?"
endTooltip
beginPopup "Button Popup" >>= whenTrue do
2021-01-24 17:35:00 +00:00
button "Close" >>= whenTrue closeCurrentPopup
endPopup
2021-01-24 16:58:52 +00:00
sameLine >> smallButton "Click me" >>= \case
2021-01-24 15:27:03 +00:00
True -> putStrLn "Oh hi Mark"
False -> return ()
sameLine >> arrowButton "Arrow" ImGuiDir_Up
2021-01-24 15:54:39 +00:00
2021-01-24 16:58:52 +00:00
sameLine >> checkbox "Check!" checked >>= \case
2021-01-24 15:56:14 +00:00
True -> readIORef checked >>= print
False -> return ()
2021-01-24 17:00:25 +00:00
separator
dragFloat3 "Slider" slider 0.1 0.0 1.0
2021-01-24 16:03:18 +00:00
progressBar 0.314 (Just "Pi")
beginChild "Child" (ImVec2 0 0) True ImGuiWindowFlags_None
beginCombo "Label" "Preview" >>= whenTrue do
selectable "Testing 1"
selectable "Testing 2"
endCombo
combo "Simple" selected [ "1", "2", "3" ]
endChild
text "ListClipper"
withChildOpen "##fixed" (ImVec2 0 200) True ImGuiWindowFlags_None do
let lotsOfItems = Vector.generate 50 (mappend "Item " . show)
withListClipper Nothing lotsOfItems text
text "ListClipper, Haskell-powered"
withChildOpen "##infinite" (ImVec2 0 200) True ImGuiWindowFlags_None do
let infiniteItems = map (mappend "Item " . show) [0 :: Int ..]
withListClipper Nothing infiniteItems text
text "Ethereal ListClipper"
withChildOpen "##ethereal" (ImVec2 0 200) True ImGuiWindowFlags_None do
withListClipper Nothing (ClipRange (0 :: Int) 1000) $
text . mappend "Item " . show
2021-01-24 20:23:58 +00:00
plotHistogram "A histogram" [ 10, 10, 20, 30, 90 ]
2021-01-25 09:11:46 +00:00
colorPicker3 "Test" color
treeNode "Tree Node 1" >>= whenTrue do
treeNode "Tree Node 2" >>= whenTrue do
treePop
treeNode "Tree Node 3" >>= whenTrue do
treePop
treePop
2021-01-24 16:49:28 +00:00
beginMainMenuBar >>= whenTrue do
beginMenu "Hello" >>= whenTrue do
menuItem "Hello"
endMenu
beginMenu "World" >>= whenTrue do
menuItem "World"
endMenu
endMainMenuBar
2021-01-24 15:27:03 +00:00
end
render
glClear GL_COLOR_BUFFER_BIT
2021-02-06 14:44:58 +00:00
openGL3RenderDrawData =<< getDrawData
2021-01-24 15:27:03 +00:00
2021-08-30 17:08:23 +00:00
glSwapWindow window
2021-01-24 15:27:03 +00:00
2021-08-30 17:08:23 +00:00
if shouldQuit
then return ()
else loop window checked color slider r pos size' selected tab1Ref tab2Ref
2021-01-24 16:49:38 +00:00
where
2021-08-30 17:08:23 +00:00
checkEvents = do
2021-01-24 16:49:38 +00:00
ev <- pollEventWithImGui
case ev of
Nothing -> return False
Just Event{ eventPayload } -> do
let isQuit = case eventPayload of
QuitEvent -> True
_ -> False
2021-08-30 17:08:23 +00:00
(isQuit ||) <$> checkEvents
whenTrue :: IO () -> Bool -> IO ()
whenTrue io True = io
2021-08-30 17:08:23 +00:00
whenTrue _io False = return ()