dear-imgui.hs/src/DearImGui.hs

479 lines
13 KiB
Haskell
Raw Normal View History

2021-01-24 15:27:03 +00:00
{-# LANGUAGE BlockArguments #-}
2021-01-24 15:56:14 +00:00
{-# LANGUAGE FlexibleContexts #-}
2021-01-24 15:27:03 +00:00
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
2021-01-24 15:54:39 +00:00
{-# LANGUAGE PatternSynonyms #-}
2021-01-24 15:27:03 +00:00
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TemplateHaskell #-}
module DearImGui
( -- * Context Creation and Access
Context(..)
, createContext
, destroyContext
-- * Main
, newFrame
, endFrame
, render
, DrawData(..)
, getDrawData
, checkVersion
-- ** SDL2
, sdl2InitForOpenGL
, sdl2NewFrame
, sdl2Shutdown
, pollEventWithImGui
-- ** OpenGL 2
, openGL2Init
, openGL2Shutdown
, openGL2NewFrame
, openGL2RenderDrawData
-- * Demo, Debug, Information
, showDemoWindow
, showMetricsWindow
, showAboutWindow
, showUserGuide
, getVersion
-- * Styles
, styleColorsDark
, styleColorsLight
, styleColorsClassic
-- * Windows
, begin
, end
-- * Widgets
-- ** Text
, text
-- ** Main
, button
, smallButton
2021-01-24 15:54:39 +00:00
, arrowButton
2021-01-24 15:56:14 +00:00
, checkbox
2021-01-24 16:03:18 +00:00
, progressBar
2021-01-24 15:56:23 +00:00
, bullet
2021-01-24 15:54:39 +00:00
-- ** Combo Box
, beginCombo
, endCombo
-- ** Selectables
, selectable
2021-01-24 16:49:28 +00:00
-- ** Menus
, beginMenuBar
, endMenuBar
, beginMainMenuBar
, endMainMenuBar
, beginMenu
, endMenu
, menuItem
2021-01-24 15:54:39 +00:00
-- * Types
, ImGuiDir
, pattern ImGuiDirLeft
, pattern ImGuiDirRight
, pattern ImGuiDirUp
, pattern ImGuiDirDown
2021-01-24 15:27:03 +00:00
)
where
2021-01-24 16:34:36 +00:00
import Control.Monad ( when )
import Control.Monad.IO.Class ( MonadIO, liftIO )
2021-01-24 15:56:14 +00:00
import Data.Bool
import Data.StateVar
2021-01-24 15:27:03 +00:00
import Foreign
2021-01-24 15:56:14 +00:00
import Foreign.C
2021-01-24 15:27:03 +00:00
import qualified Language.C.Inline as C
import qualified Language.C.Inline.Cpp as Cpp
import SDL
import SDL.Internal.Types
import SDL.Raw.Enum as Raw
import qualified SDL.Raw.Event as Raw
import Unsafe.Coerce ( unsafeCoerce )
C.context (Cpp.cppCtx <> C.bsCtx)
C.include "imgui.h"
C.include "backends/imgui_impl_opengl2.h"
C.include "backends/imgui_impl_sdl.h"
C.include "SDL.h"
C.include "SDL_opengl.h"
Cpp.using "namespace ImGui"
-- | Wraps @ImGuiContext*@.
newtype Context = Context (Ptr ())
-- | Wraps @ImGui::CreateContext()@.
2021-01-24 16:34:36 +00:00
createContext :: MonadIO m => m Context
createContext = liftIO do
2021-01-24 15:27:03 +00:00
Context <$> [C.exp| void* { CreateContext() } |]
-- | Wraps @ImGui::DestroyContext()@.
2021-01-24 16:34:36 +00:00
destroyContext :: MonadIO m => Context -> m ()
destroyContext (Context contextPtr) = liftIO do
2021-01-24 15:27:03 +00:00
[C.exp| void { DestroyContext((ImGuiContext*)$(void* contextPtr)); } |]
-- | Start a new Dear ImGui frame, you can submit any command from this point
-- until 'render'/'endFrame'.
--
-- Wraps @ImGui::NewFrame()@.
2021-01-24 16:34:36 +00:00
newFrame :: MonadIO m => m ()
newFrame = liftIO do
[C.exp| void { ImGui::NewFrame(); } |]
2021-01-24 15:27:03 +00:00
-- | Ends the Dear ImGui frame. automatically called by 'render'. If you don't
-- need to render data (skipping rendering) you may call 'endFrame' without
-- 'render'... but you'll have wasted CPU already! If you don't need to render,
-- better to not create any windows and not call 'newFrame' at all!
2021-01-24 16:34:36 +00:00
endFrame :: MonadIO m => m ()
endFrame = liftIO do
[C.exp| void { ImGui::EndFrame(); } |]
2021-01-24 15:27:03 +00:00
-- | Ends the Dear ImGui frame, finalize the draw data. You can then get call
-- 'getDrawData'.
2021-01-24 16:34:36 +00:00
render :: MonadIO m => m ()
render = liftIO do
[C.exp| void { ImGui::Render(); } |]
2021-01-24 15:27:03 +00:00
-- | Wraps @ImDrawData*@.
newtype DrawData = DrawData (Ptr ())
-- | Valid after 'render' and until the next call to 'newFrame'. This is what
-- you have to render.
2021-01-24 16:34:36 +00:00
getDrawData :: MonadIO m => m DrawData
getDrawData = liftIO do
DrawData <$> [C.exp| void* { ImGui::GetDrawData() } |]
2021-01-24 15:27:03 +00:00
-- | Wraps @IMGUI_CHECKVERSION()@
2021-01-24 16:34:36 +00:00
checkVersion :: MonadIO m => m ()
checkVersion = liftIO do
2021-01-24 15:27:03 +00:00
[C.exp| void { IMGUI_CHECKVERSION(); } |]
-- | Wraps @ImGui_ImplSDL2_InitForOpenGL@.
2021-01-24 16:34:36 +00:00
sdl2InitForOpenGL :: MonadIO m => Window -> GLContext -> m ()
sdl2InitForOpenGL (Window windowPtr) glContext = liftIO do
2021-01-24 15:27:03 +00:00
[C.exp| void { ImGui_ImplSDL2_InitForOpenGL((SDL_Window*)$(void* windowPtr), $(void* glContextPtr)); } |]
where
glContextPtr :: Ptr ()
glContextPtr = unsafeCoerce glContext
-- | Wraps @ImGui_ImplSDL2_NewFrame@.
2021-01-24 16:34:36 +00:00
sdl2NewFrame :: MonadIO m => Window -> m ()
sdl2NewFrame (Window windowPtr) = liftIO do
2021-01-24 15:27:03 +00:00
[C.exp| void { ImGui_ImplSDL2_NewFrame((SDL_Window*)($(void* windowPtr))); } |]
-- | Wraps @ImGui_ImplSDL2_Shutdown@.
2021-01-24 16:34:36 +00:00
sdl2Shutdown :: MonadIO m => m ()
sdl2Shutdown = liftIO do
[C.exp| void { ImGui_ImplSDL2_Shutdown(); } |]
2021-01-24 15:27:03 +00:00
-- | Call the SDL2 'pollEvent' function, while also dispatching the event to
-- Dear ImGui. You should use this in your application instead of 'pollEvent'.
2021-01-24 16:34:36 +00:00
pollEventWithImGui :: MonadIO m => m (Maybe Event)
pollEventWithImGui = liftIO do
alloca \evPtr -> do
pumpEvents
2021-01-24 15:27:03 +00:00
2021-01-24 16:34:36 +00:00
-- We use NULL first to check if there's an event.
nEvents <- Raw.peepEvents evPtr 1 Raw.SDL_PEEKEVENT Raw.SDL_FIRSTEVENT Raw.SDL_LASTEVENT
2021-01-24 15:27:03 +00:00
2021-01-24 16:34:36 +00:00
when (nEvents > 0) do
let evPtr' = castPtr evPtr :: Ptr ()
[C.exp| void { ImGui_ImplSDL2_ProcessEvent((SDL_Event*) $(void* evPtr')) } |]
2021-01-24 15:27:03 +00:00
2021-01-24 16:34:36 +00:00
pollEvent
2021-01-24 15:27:03 +00:00
-- | Wraps @ImGui_ImplOpenGL2_Init@.
2021-01-24 16:34:36 +00:00
openGL2Init :: MonadIO m => m ()
openGL2Init = liftIO do
[C.exp| void { ImGui_ImplOpenGL2_Init(); } |]
2021-01-24 15:27:03 +00:00
-- | Wraps @ImGui_ImplOpenGL2_Shutdown@.
2021-01-24 16:34:36 +00:00
openGL2Shutdown :: MonadIO m => m ()
openGL2Shutdown = liftIO do
[C.exp| void { ImGui_ImplOpenGL2_Shutdown(); } |]
2021-01-24 15:27:03 +00:00
-- | Wraps @ImGui_ImplOpenGL2_NewFrame@.
2021-01-24 16:34:36 +00:00
openGL2NewFrame :: MonadIO m => m ()
openGL2NewFrame = liftIO do
[C.exp| void { ImGui_ImplOpenGL2_NewFrame(); } |]
2021-01-24 15:27:03 +00:00
-- | Wraps @ImGui_ImplOpenGL2_RenderDrawData@.
2021-01-24 16:34:36 +00:00
openGL2RenderDrawData :: MonadIO m => DrawData -> m ()
openGL2RenderDrawData (DrawData ptr) = liftIO do
[C.exp| void { ImGui_ImplOpenGL2_RenderDrawData((ImDrawData*) $( void* ptr )) } |]
2021-01-24 15:27:03 +00:00
-- | Create demo window. Demonstrate most ImGui features. Call this to learn
-- about the library! Try to make it always available in your application!
2021-01-24 16:34:36 +00:00
showDemoWindow :: MonadIO m => m ()
showDemoWindow = liftIO do
[C.exp| void { ImGui::ShowDemoWindow(); } |]
2021-01-24 15:27:03 +00:00
-- | Create Metrics/Debugger window. Display Dear ImGui internals: windows, draw
-- commands, various internal state, etc.
2021-01-24 16:34:36 +00:00
showMetricsWindow :: MonadIO m => m ()
showMetricsWindow = liftIO do
[C.exp| void { ImGui::ShowMetricsWindow(); } |]
2021-01-24 15:27:03 +00:00
-- | Create About window. display Dear ImGui version, credits and build/system
-- information.
2021-01-24 16:34:36 +00:00
showAboutWindow :: MonadIO m => m ()
showAboutWindow = liftIO do
[C.exp| void { ShowAboutWindow(); } |]
2021-01-24 15:27:03 +00:00
-- | Add basic help/info block (not a window): how to manipulate ImGui as a
-- end-user (mouse/keyboard controls).
2021-01-24 16:34:36 +00:00
showUserGuide :: MonadIO m => m ()
showUserGuide = liftIO do
[C.exp| void { ShowUserGuide() } |]
2021-01-24 15:27:03 +00:00
-- | Get the compiled version string e.g. "1.80 WIP" (essentially the value for
-- @IMGUI_VERSION@ from the compiled version of @imgui.cpp@).
2021-01-24 16:34:36 +00:00
getVersion :: MonadIO m => m String
getVersion = liftIO do
peekCString =<< [C.exp| const char* { GetVersion() } |]
2021-01-24 15:27:03 +00:00
-- | New, recommended style (default).
--
-- Wraps @ImGui::StyleColorsDark()@.
2021-01-24 16:34:36 +00:00
styleColorsDark :: MonadIO m => m ()
styleColorsDark = liftIO do
[C.exp| void { StyleColorsDark(); } |]
2021-01-24 15:27:03 +00:00
-- | Best used with borders and a custom, thicker font.
--
-- Wraps @ImGui::StyleColorsLight()@.
2021-01-24 16:34:36 +00:00
styleColorsLight :: MonadIO m => m ()
styleColorsLight = liftIO do
[C.exp| void { StyleColorsLight(); } |]
2021-01-24 15:27:03 +00:00
-- | Classic ImGui style.
--
-- Wraps @ImGui::StyleColorsClasic()@.
2021-01-24 16:34:36 +00:00
styleColorsClassic :: MonadIO m => m ()
styleColorsClassic = liftIO do
[C.exp| void { StyleColorsClassic(); } |]
2021-01-24 15:27:03 +00:00
-- | Push window to the stack and start appending to it.
--
-- Returns 'False' to indicate the window is collapsed or fully clipped, so you
-- may early out and omit submitting anything to the window. Always call a
-- matching 'end' for each 'begin' call, regardless of its return value!
--
-- Wraps @ImGui::Begin()@.
2021-01-24 16:34:36 +00:00
begin :: MonadIO m => String -> m Bool
begin name = liftIO do
withCString name \namePtr ->
(1 ==) <$> [C.exp| bool { ImGui::Begin($(char* namePtr)) } |]
2021-01-24 15:27:03 +00:00
-- | Pop window from the stack.
--
-- Wraps @ImGui::End()@.
2021-01-24 16:34:36 +00:00
end :: MonadIO m => m ()
end = liftIO do
[C.exp| void { ImGui::End(); } |]
2021-01-24 15:27:03 +00:00
-- | Formatted text.
--
-- Wraps @ImGui::Text()@.
2021-01-24 16:34:36 +00:00
text :: MonadIO m => String -> m ()
text t = liftIO do
withCString t \textPtr ->
[C.exp| void { Text($(char* textPtr)) } |]
2021-01-24 15:27:03 +00:00
-- | A button. Returns 'True' when clicked.
--
-- Wraps @ImGui::Button()@.
2021-01-24 16:34:36 +00:00
button :: MonadIO m => String -> m Bool
button label = liftIO do
withCString label \labelPtr ->
(1 ==) <$> [C.exp| bool { Button($(char* labelPtr)) } |]
2021-01-24 15:27:03 +00:00
-- | Button with @FramePadding=(0,0)@ to easily embed within text.
--
-- Wraps @ImGui::SmallButton()@.
2021-01-24 16:34:36 +00:00
smallButton :: MonadIO m => String -> m Bool
smallButton label = liftIO do
withCString label \labelPtr ->
(1 ==) <$> [C.exp| bool { SmallButton($(char* labelPtr)) } |]
2021-01-24 15:54:39 +00:00
-- | Square button with an arrow shape.
--
-- Wraps @ImGui::ArrowButton()@.
2021-01-24 16:34:36 +00:00
arrowButton :: MonadIO m => String -> ImGuiDir -> m Bool
arrowButton strId (ImGuiDir dir) = liftIO do
withCString strId \strIdPtr ->
(1 ==) <$> [C.exp| bool { ArrowButton($(char* strIdPtr), $(int dir)) } |]
2021-01-24 15:54:39 +00:00
2021-01-24 15:56:14 +00:00
-- | Wraps @ImGui::Checkbox()@.
2021-01-24 16:34:36 +00:00
checkbox :: (HasSetter ref Bool, HasGetter ref Bool, MonadIO m) => String -> ref -> m Bool
checkbox label ref = liftIO do
2021-01-24 15:56:14 +00:00
currentValue <- get ref
with (bool 0 1 currentValue :: CBool) \boolPtr -> do
changed <- withCString label \labelPtr ->
(1 ==) <$> [C.exp| bool { Checkbox($(char* labelPtr), $(bool* boolPtr)) } |]
newValue <- peek boolPtr
ref $=! (newValue == 1)
return changed
2021-01-24 16:34:36 +00:00
progressBar :: MonadIO m => Float -> Maybe String -> m ()
progressBar progress overlay = liftIO do
withCStringOrNull overlay \overlayPtr ->
[C.exp| void { ProgressBar($(float c'progress), ImVec2(-FLT_MIN, 0), $(char* overlayPtr)) } |]
2021-01-24 16:03:18 +00:00
where
c'progress :: CFloat
c'progress = realToFrac progress
2021-01-24 15:56:23 +00:00
-- | Draw a small circle + keep the cursor on the same line. Advance cursor x
-- position by 'getTreeNodeToLabelSpacing', same distance that 'treeNode' uses.
2021-01-24 16:34:36 +00:00
bullet :: MonadIO m => m ()
bullet = liftIO do
[C.exp| void { Bullet() } |]
2021-01-24 15:56:23 +00:00
-- | Begin creating a combo box with a given label and preview value.
--
-- Returns 'True' if the combo box is open. In this state, you should populate
-- the contents of the combo box - for example, by calling 'selectable'.
--
-- Wraps @ImGui::BeginCombo()@.
2021-01-24 16:34:36 +00:00
beginCombo :: MonadIO m => String -> String -> m Bool
beginCombo label previewValue = liftIO $
withCString label \labelPtr ->
withCString previewValue \previewValuePtr ->
(1 ==) <$> [C.exp| bool { BeginCombo($(char* labelPtr), $(char* previewValuePtr)) } |]
-- | Only call 'endCombo' if 'beginCombon' returns 'True'!
--
-- Wraps @ImGui::EndCombo()@.
2021-01-24 16:34:36 +00:00
endCombo :: MonadIO m => m ()
endCombo = liftIO do
[C.exp| void { EndCombo() } |]
-- | Wraps @ImGui::Selectable()@.
2021-01-24 16:34:36 +00:00
selectable :: MonadIO m => String -> m Bool
selectable label = liftIO do
withCString label \labelPtr ->
(1 == ) <$> [C.exp| bool { Selectable($(char* labelPtr)) } |]
2021-01-24 16:49:28 +00:00
-- | Append to menu-bar of current window (requires 'ImGuiWindowFlagsMenuBar'
-- flag set on parent window).
--
-- Wraps @ImGui::BeginMenuBar()@.
beginMenuBar :: MonadIO m => m Bool
beginMenuBar = liftIO do
(1 == ) <$> [C.exp| bool { BeginMenuBar() } |]
-- | Only call 'endMenuBar' if 'beginMenuBar' returns true!
--
-- Wraps @ImGui::EndMenuBar()@.
endMenuBar :: MonadIO m => m ()
endMenuBar = liftIO do
[C.exp| void { EndMenuBar(); } |]
-- | Create and append to a full screen menu-bar.
--
-- Wraps @ImGui::BeginMainMenuBar()@.
beginMainMenuBar :: MonadIO m => m Bool
beginMainMenuBar = liftIO do
(1 == ) <$> [C.exp| bool { BeginMainMenuBar() } |]
-- | Only call 'endMainMenuBar' if 'beginMainMenuBar' returns true!
--
-- Wraps @ImGui::EndMainMenuBar()@.
endMainMenuBar :: MonadIO m => m ()
endMainMenuBar = liftIO do
[C.exp| void { EndMainMenuBar(); } |]
-- | Create a sub-menu entry.
--
-- Wraps @ImGui::BeginMenu()@.
beginMenu :: MonadIO m => String -> m Bool
beginMenu label = liftIO do
withCString label \labelPtr ->
(1 == ) <$> [C.exp| bool { BeginMenu($(char* labelPtr)) } |]
-- | Only call 'endMenu' if 'beginMenu' returns true!
--
-- Wraps @ImGui::EndMenu()@.
endMenu :: MonadIO m => m ()
endMenu = liftIO do
[C.exp| void { EndMenu(); } |]
-- Return true when activated. Shortcuts are displayed for convenience but not
-- processed by ImGui at the moment
--
-- Wraps @ImGui::MenuItem()@
menuItem :: MonadIO m => String -> m Bool
menuItem label = liftIO do
withCString label \labelPtr ->
(1 ==) <$> [C.exp| bool { MenuItem($(char* labelPtr)) } |]
2021-01-24 15:54:39 +00:00
-- | A cardinal direction.
newtype ImGuiDir = ImGuiDir CInt
pattern ImGuiDirLeft, ImGuiDirRight, ImGuiDirUp, ImGuiDirDown :: ImGuiDir
pattern ImGuiDirLeft = ImGuiDir 0
pattern ImGuiDirRight = ImGuiDir 1
pattern ImGuiDirUp = ImGuiDir 2
pattern ImGuiDirDown = ImGuiDir 3
2021-01-24 16:03:18 +00:00
withCStringOrNull :: Maybe String -> (Ptr CChar -> IO a) -> IO a
withCStringOrNull Nothing k = k nullPtr
withCStringOrNull (Just s) k = withCString s k