Skip to content

Commit 4398950

Browse files
committed
Initial work
1 parent e2a9ec3 commit 4398950

File tree

5 files changed

+382
-0
lines changed

5 files changed

+382
-0
lines changed

.gitmodules

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,3 @@
1+
[submodule "imgui"]
2+
path = imgui
3+
url = https://github.com/ocornut/imgui

Main.hs

Lines changed: 67 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,67 @@
1+
{-# LANGUAGE BlockArguments #-}
2+
{-# LANGUAGE LambdaCase #-}
3+
{-# LANGUAGE NamedFieldPuns #-}
4+
{-# LANGUAGE OverloadedStrings #-}
5+
6+
module Main (main) where
7+
8+
import DearImGui
9+
import Control.Exception
10+
import Graphics.GL
11+
import SDL
12+
13+
main :: IO ()
14+
main = do
15+
initializeAll
16+
17+
bracket (createWindow "Hello, Dear ImGui!" defaultWindow { windowGraphicsContext = OpenGLContext defaultOpenGL }) destroyWindow \w ->
18+
bracket (glCreateContext w) glDeleteContext \glContext ->
19+
bracket createContext destroyContext \_imguiContext ->
20+
bracket_ (sdl2InitForOpenGL w glContext) sdl2Shutdown $
21+
bracket_ openGL2Init openGL2Shutdown do
22+
checkVersion
23+
styleColorsLight
24+
openGL2Init
25+
26+
loop w
27+
28+
openGL2Shutdown
29+
30+
loop :: Window -> IO ()
31+
loop w = do
32+
ev <- pollEventWithImGui
33+
34+
openGL2NewFrame
35+
sdl2NewFrame w
36+
newFrame
37+
38+
-- showDemoWindow
39+
-- showMetricsWindow
40+
-- showAboutWindow
41+
-- showUserGuide
42+
43+
begin "My Window"
44+
text "Hello!"
45+
46+
button "Click me" >>= \case
47+
True -> putStrLn "Oh hi Mark"
48+
False -> return ()
49+
50+
smallButton "Click me" >>= \case
51+
True -> putStrLn "Oh hi Mark"
52+
False -> return ()
53+
54+
end
55+
56+
render
57+
58+
glClear GL_COLOR_BUFFER_BIT
59+
openGL2RenderDrawData =<< getDrawData
60+
61+
glSwapWindow w
62+
63+
case ev of
64+
Nothing -> loop w
65+
Just Event{ eventPayload } -> case eventPayload of
66+
QuitEvent -> return ()
67+
_ -> loop w

hs-dear-imgui.cabal

Lines changed: 31 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,31 @@
1+
cabal-version: 3.0
2+
name: dear-imgui
3+
version: 1.0.0
4+
build-type: Simple
5+
6+
library
7+
exposed-modules: DearImGui
8+
hs-source-dirs: src
9+
default-language: Haskell2010
10+
ghc-options: -Wall
11+
cxx-sources:
12+
imgui/imgui.cpp
13+
imgui/backends/imgui_impl_opengl2.cpp
14+
imgui/backends/imgui_impl_sdl.cpp
15+
imgui/imgui_tables.cpp
16+
imgui/imgui_widgets.cpp
17+
imgui/imgui_draw.cpp
18+
imgui/imgui_demo.cpp
19+
cxx-options: -std=c++11
20+
extra-libraries: stdc++
21+
pkgconfig-depends: sdl2
22+
include-dirs: imgui
23+
build-depends: base, inline-c, inline-c-cpp, sdl2
24+
extra-libraries: GL
25+
26+
27+
executable test
28+
main-is: Main.hs
29+
default-language: Haskell2010
30+
build-depends: base, sdl2, gl, dear-imgui
31+
ghc-options: -Wall

imgui

Submodule imgui added at 58075c4

src/DearImGui.hs

Lines changed: 280 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,280 @@
1+
{-# LANGUAGE BlockArguments #-}
2+
{-# LANGUAGE NamedFieldPuns #-}
3+
{-# LANGUAGE OverloadedStrings #-}
4+
{-# LANGUAGE QuasiQuotes #-}
5+
{-# LANGUAGE TemplateHaskell #-}
6+
7+
module DearImGui
8+
( -- * Context Creation and Access
9+
Context(..)
10+
, createContext
11+
, destroyContext
12+
13+
-- * Main
14+
, newFrame
15+
, endFrame
16+
, render
17+
, DrawData(..)
18+
, getDrawData
19+
, checkVersion
20+
21+
-- ** SDL2
22+
, sdl2InitForOpenGL
23+
, sdl2NewFrame
24+
, sdl2Shutdown
25+
, pollEventWithImGui
26+
27+
-- ** OpenGL 2
28+
, openGL2Init
29+
, openGL2Shutdown
30+
, openGL2NewFrame
31+
, openGL2RenderDrawData
32+
33+
-- * Demo, Debug, Information
34+
, showDemoWindow
35+
, showMetricsWindow
36+
, showAboutWindow
37+
, showUserGuide
38+
, getVersion
39+
40+
-- * Styles
41+
, styleColorsDark
42+
, styleColorsLight
43+
, styleColorsClassic
44+
45+
-- * Windows
46+
, begin
47+
, end
48+
49+
-- * Widgets
50+
-- ** Text
51+
, text
52+
53+
-- ** Main
54+
, button
55+
, smallButton
56+
)
57+
where
58+
59+
import Control.Monad ( when )
60+
import Foreign
61+
import Foreign.C.String
62+
import qualified Language.C.Inline as C
63+
import qualified Language.C.Inline.Cpp as Cpp
64+
import SDL
65+
import SDL.Internal.Types
66+
import SDL.Raw.Enum as Raw
67+
import qualified SDL.Raw.Event as Raw
68+
import Unsafe.Coerce ( unsafeCoerce )
69+
70+
C.context (Cpp.cppCtx <> C.bsCtx)
71+
C.include "imgui.h"
72+
C.include "backends/imgui_impl_opengl2.h"
73+
C.include "backends/imgui_impl_sdl.h"
74+
C.include "SDL.h"
75+
C.include "SDL_opengl.h"
76+
Cpp.using "namespace ImGui"
77+
78+
79+
-- | Wraps @ImGuiContext*@.
80+
newtype Context = Context (Ptr ())
81+
82+
83+
-- | Wraps @ImGui::CreateContext()@.
84+
createContext :: IO Context
85+
createContext =
86+
Context <$> [C.exp| void* { CreateContext() } |]
87+
88+
89+
-- | Wraps @ImGui::DestroyContext()@.
90+
destroyContext :: Context -> IO ()
91+
destroyContext (Context contextPtr) =
92+
[C.exp| void { DestroyContext((ImGuiContext*)$(void* contextPtr)); } |]
93+
94+
95+
-- | Start a new Dear ImGui frame, you can submit any command from this point
96+
-- until 'render'/'endFrame'.
97+
--
98+
-- Wraps @ImGui::NewFrame()@.
99+
newFrame :: IO ()
100+
newFrame = [C.exp| void { ImGui::NewFrame(); } |]
101+
102+
103+
-- | Ends the Dear ImGui frame. automatically called by 'render'. If you don't
104+
-- need to render data (skipping rendering) you may call 'endFrame' without
105+
-- 'render'... but you'll have wasted CPU already! If you don't need to render,
106+
-- better to not create any windows and not call 'newFrame' at all!
107+
endFrame :: IO ()
108+
endFrame = [C.exp| void { ImGui::EndFrame(); } |]
109+
110+
111+
-- | Ends the Dear ImGui frame, finalize the draw data. You can then get call
112+
-- 'getDrawData'.
113+
render :: IO ()
114+
render = [C.exp| void { ImGui::Render(); } |]
115+
116+
117+
-- | Wraps @ImDrawData*@.
118+
newtype DrawData = DrawData (Ptr ())
119+
120+
121+
-- | Valid after 'render' and until the next call to 'newFrame'. This is what
122+
-- you have to render.
123+
getDrawData :: IO DrawData
124+
getDrawData = DrawData <$> [C.exp| void* { ImGui::GetDrawData() } |]
125+
126+
127+
-- | Wraps @IMGUI_CHECKVERSION()@
128+
checkVersion :: IO ()
129+
checkVersion =
130+
[C.exp| void { IMGUI_CHECKVERSION(); } |]
131+
132+
133+
-- | Wraps @ImGui_ImplSDL2_InitForOpenGL@.
134+
sdl2InitForOpenGL :: Window -> GLContext -> IO ()
135+
sdl2InitForOpenGL (Window windowPtr) glContext =
136+
[C.exp| void { ImGui_ImplSDL2_InitForOpenGL((SDL_Window*)$(void* windowPtr), $(void* glContextPtr)); } |]
137+
where
138+
glContextPtr :: Ptr ()
139+
glContextPtr = unsafeCoerce glContext
140+
141+
142+
-- | Wraps @ImGui_ImplSDL2_NewFrame@.
143+
sdl2NewFrame :: Window -> IO ()
144+
sdl2NewFrame (Window windowPtr) =
145+
[C.exp| void { ImGui_ImplSDL2_NewFrame((SDL_Window*)($(void* windowPtr))); } |]
146+
147+
148+
-- | Wraps @ImGui_ImplSDL2_Shutdown@.
149+
sdl2Shutdown :: IO ()
150+
sdl2Shutdown = [C.exp| void { ImGui_ImplSDL2_Shutdown(); } |]
151+
152+
153+
-- | Call the SDL2 'pollEvent' function, while also dispatching the event to
154+
-- Dear ImGui. You should use this in your application instead of 'pollEvent'.
155+
pollEventWithImGui :: IO (Maybe Event)
156+
pollEventWithImGui = alloca \evPtr -> do
157+
pumpEvents
158+
159+
-- We use NULL first to check if there's an event.
160+
nEvents <- Raw.peepEvents evPtr 1 Raw.SDL_PEEKEVENT Raw.SDL_FIRSTEVENT Raw.SDL_LASTEVENT
161+
162+
when (nEvents > 0) do
163+
let evPtr' = castPtr evPtr :: Ptr ()
164+
[C.exp| void { ImGui_ImplSDL2_ProcessEvent((SDL_Event*) $(void* evPtr')) } |]
165+
166+
pollEvent
167+
168+
169+
-- | Wraps @ImGui_ImplOpenGL2_Init@.
170+
openGL2Init :: IO ()
171+
openGL2Init = [C.exp| void { ImGui_ImplOpenGL2_Init(); } |]
172+
173+
174+
-- | Wraps @ImGui_ImplOpenGL2_Shutdown@.
175+
openGL2Shutdown :: IO ()
176+
openGL2Shutdown = [C.exp| void { ImGui_ImplOpenGL2_Shutdown(); } |]
177+
178+
179+
-- | Wraps @ImGui_ImplOpenGL2_NewFrame@.
180+
openGL2NewFrame :: IO ()
181+
openGL2NewFrame = [C.exp| void { ImGui_ImplOpenGL2_NewFrame(); } |]
182+
183+
184+
-- | Wraps @ImGui_ImplOpenGL2_RenderDrawData@.
185+
openGL2RenderDrawData :: DrawData -> IO ()
186+
openGL2RenderDrawData (DrawData ptr) = [C.exp| void { ImGui_ImplOpenGL2_RenderDrawData((ImDrawData*) $( void* ptr )) } |]
187+
188+
189+
-- | Create demo window. Demonstrate most ImGui features. Call this to learn
190+
-- about the library! Try to make it always available in your application!
191+
showDemoWindow :: IO ()
192+
showDemoWindow = [C.exp| void { ImGui::ShowDemoWindow(); } |]
193+
194+
195+
-- | Create Metrics/Debugger window. Display Dear ImGui internals: windows, draw
196+
-- commands, various internal state, etc.
197+
showMetricsWindow :: IO ()
198+
showMetricsWindow = [C.exp| void { ImGui::ShowMetricsWindow(); } |]
199+
200+
201+
-- | Create About window. display Dear ImGui version, credits and build/system
202+
-- information.
203+
showAboutWindow :: IO ()
204+
showAboutWindow = [C.exp| void { ShowAboutWindow(); } |]
205+
206+
207+
-- | Add basic help/info block (not a window): how to manipulate ImGui as a
208+
-- end-user (mouse/keyboard controls).
209+
showUserGuide :: IO ()
210+
showUserGuide = [C.exp| void { ShowUserGuide() } |]
211+
212+
213+
-- | Get the compiled version string e.g. "1.80 WIP" (essentially the value for
214+
-- @IMGUI_VERSION@ from the compiled version of @imgui.cpp@).
215+
getVersion :: IO String
216+
getVersion = peekCString =<< [C.exp| const char* { GetVersion() } |]
217+
218+
219+
-- | New, recommended style (default).
220+
--
221+
-- Wraps @ImGui::StyleColorsDark()@.
222+
styleColorsDark :: IO ()
223+
styleColorsDark = [C.exp| void { StyleColorsDark(); } |]
224+
225+
226+
-- | Best used with borders and a custom, thicker font.
227+
--
228+
-- Wraps @ImGui::StyleColorsLight()@.
229+
styleColorsLight :: IO ()
230+
styleColorsLight = [C.exp| void { StyleColorsLight(); } |]
231+
232+
233+
-- | Classic ImGui style.
234+
--
235+
-- Wraps @ImGui::StyleColorsClasic()@.
236+
styleColorsClassic :: IO ()
237+
styleColorsClassic = [C.exp| void { StyleColorsClassic(); } |]
238+
239+
240+
-- | Push window to the stack and start appending to it.
241+
--
242+
-- Returns 'False' to indicate the window is collapsed or fully clipped, so you
243+
-- may early out and omit submitting anything to the window. Always call a
244+
-- matching 'end' for each 'begin' call, regardless of its return value!
245+
--
246+
-- Wraps @ImGui::Begin()@.
247+
begin :: String -> IO Bool
248+
begin name = withCString name \namePtr ->
249+
(1 ==) <$> [C.exp| bool { ImGui::Begin($(char* namePtr)) } |]
250+
251+
252+
-- | Pop window from the stack.
253+
--
254+
-- Wraps @ImGui::End()@.
255+
end :: IO ()
256+
end = [C.exp| void { ImGui::End(); } |]
257+
258+
259+
-- | Formatted text.
260+
--
261+
-- Wraps @ImGui::Text()@.
262+
text :: String -> IO ()
263+
text t = withCString t \textPtr ->
264+
[C.exp| void { Text($(char* textPtr)) } |]
265+
266+
267+
-- | A button. Returns 'True' when clicked.
268+
--
269+
-- Wraps @ImGui::Button()@.
270+
button :: String -> IO Bool
271+
button label = withCString label \labelPtr ->
272+
(1 ==) <$> [C.exp| bool { Button($(char* labelPtr)) } |]
273+
274+
275+
-- | Button with @FramePadding=(0,0)@ to easily embed within text.
276+
--
277+
-- Wraps @ImGui::SmallButton()@.
278+
smallButton :: String -> IO Bool
279+
smallButton label = withCString label \labelPtr ->
280+
(1 ==) <$> [C.exp| bool { SmallButton($(char* labelPtr)) } |]

0 commit comments

Comments
 (0)