mirror of
https://github.com/Drezil/dear-imgui.hs.git
synced 2025-07-04 20:18:47 +02:00
add cabal flags for backend selection
This commit is contained in:
65
src/DearImGui/OpenGL.hs
Normal file
65
src/DearImGui/OpenGL.hs
Normal file
@ -0,0 +1,65 @@
|
||||
{-# LANGUAGE BlockArguments #-}
|
||||
{-# LANGUAGE FlexibleContexts #-}
|
||||
{-# LANGUAGE NamedFieldPuns #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# LANGUAGE PatternSynonyms #-}
|
||||
{-# LANGUAGE QuasiQuotes #-}
|
||||
{-# LANGUAGE TemplateHaskell #-}
|
||||
|
||||
{-|
|
||||
Module: DearImGui.OpenGL
|
||||
|
||||
OpenGL backend for Dear ImGui.
|
||||
-}
|
||||
|
||||
module DearImGui.OpenGL
|
||||
( openGL2Init
|
||||
, openGL2Shutdown
|
||||
, openGL2NewFrame
|
||||
, openGL2RenderDrawData
|
||||
)
|
||||
where
|
||||
|
||||
-- inline-c
|
||||
import qualified Language.C.Inline as C
|
||||
|
||||
-- inline-c-cpp
|
||||
import qualified Language.C.Inline.Cpp as Cpp
|
||||
|
||||
-- transformers
|
||||
import Control.Monad.IO.Class
|
||||
( MonadIO, liftIO )
|
||||
|
||||
-- DearImGui
|
||||
import DearImGui
|
||||
( DrawData(..) )
|
||||
|
||||
|
||||
C.context (Cpp.cppCtx <> C.bsCtx)
|
||||
C.include "imgui.h"
|
||||
C.include "backends/imgui_impl_opengl2.h"
|
||||
Cpp.using "namespace ImGui"
|
||||
|
||||
|
||||
-- | Wraps @ImGui_ImplOpenGL2_Init@.
|
||||
openGL2Init :: MonadIO m => m ()
|
||||
openGL2Init = liftIO do
|
||||
[C.exp| void { ImGui_ImplOpenGL2_Init(); } |]
|
||||
|
||||
|
||||
-- | Wraps @ImGui_ImplOpenGL2_Shutdown@.
|
||||
openGL2Shutdown :: MonadIO m => m ()
|
||||
openGL2Shutdown = liftIO do
|
||||
[C.exp| void { ImGui_ImplOpenGL2_Shutdown(); } |]
|
||||
|
||||
|
||||
-- | Wraps @ImGui_ImplOpenGL2_NewFrame@.
|
||||
openGL2NewFrame :: MonadIO m => m ()
|
||||
openGL2NewFrame = liftIO do
|
||||
[C.exp| void { ImGui_ImplOpenGL2_NewFrame(); } |]
|
||||
|
||||
|
||||
-- | Wraps @ImGui_ImplOpenGL2_RenderDrawData@.
|
||||
openGL2RenderDrawData :: MonadIO m => DrawData -> m ()
|
||||
openGL2RenderDrawData (DrawData ptr) = liftIO do
|
||||
[C.exp| void { ImGui_ImplOpenGL2_RenderDrawData((ImDrawData*) $( void* ptr )) } |]
|
83
src/DearImGui/SDL.hs
Normal file
83
src/DearImGui/SDL.hs
Normal file
@ -0,0 +1,83 @@
|
||||
{-# LANGUAGE BlockArguments #-}
|
||||
{-# LANGUAGE FlexibleContexts #-}
|
||||
{-# LANGUAGE NamedFieldPuns #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# LANGUAGE PatternSynonyms #-}
|
||||
{-# LANGUAGE QuasiQuotes #-}
|
||||
{-# LANGUAGE TemplateHaskell #-}
|
||||
|
||||
{-|
|
||||
Module: DearImGui.SDL
|
||||
|
||||
SDL2 specific functions backend for Dear ImGui.
|
||||
|
||||
Modules for initialising a backend with SDL2 can be found under the corresponding backend,
|
||||
e.g. "DearImGui.SDL.OpenGL".
|
||||
-}
|
||||
|
||||
module DearImGui.SDL (
|
||||
-- ** SDL2
|
||||
sdl2NewFrame
|
||||
, sdl2Shutdown
|
||||
, pollEventWithImGui
|
||||
)
|
||||
where
|
||||
|
||||
-- base
|
||||
import Control.Monad
|
||||
( when )
|
||||
import Foreign.Marshal.Alloc
|
||||
( alloca )
|
||||
import Foreign.Ptr
|
||||
( Ptr, castPtr )
|
||||
|
||||
-- inline-c
|
||||
import qualified Language.C.Inline as C
|
||||
|
||||
-- inline-c-cpp
|
||||
import qualified Language.C.Inline.Cpp as Cpp
|
||||
|
||||
-- sdl2
|
||||
import SDL
|
||||
import SDL.Internal.Types
|
||||
import SDL.Raw.Enum as Raw
|
||||
import qualified SDL.Raw.Event as Raw
|
||||
|
||||
-- transformers
|
||||
import Control.Monad.IO.Class
|
||||
( MonadIO, liftIO )
|
||||
|
||||
|
||||
C.context (Cpp.cppCtx <> C.bsCtx)
|
||||
C.include "imgui.h"
|
||||
C.include "backends/imgui_impl_sdl.h"
|
||||
C.include "SDL.h"
|
||||
Cpp.using "namespace ImGui"
|
||||
|
||||
|
||||
-- | Wraps @ImGui_ImplSDL2_NewFrame@.
|
||||
sdl2NewFrame :: MonadIO m => Window -> m ()
|
||||
sdl2NewFrame (Window windowPtr) = liftIO do
|
||||
[C.exp| void { ImGui_ImplSDL2_NewFrame((SDL_Window*)($(void* windowPtr))); } |]
|
||||
|
||||
|
||||
-- | Wraps @ImGui_ImplSDL2_Shutdown@.
|
||||
sdl2Shutdown :: MonadIO m => m ()
|
||||
sdl2Shutdown = liftIO do
|
||||
[C.exp| void { ImGui_ImplSDL2_Shutdown(); } |]
|
||||
|
||||
-- | Call the SDL2 'pollEvent' function, while also dispatching the event to
|
||||
-- Dear ImGui. You should use this in your application instead of 'pollEvent'.
|
||||
pollEventWithImGui :: MonadIO m => m (Maybe Event)
|
||||
pollEventWithImGui = liftIO do
|
||||
alloca \evPtr -> do
|
||||
pumpEvents
|
||||
|
||||
-- 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
|
||||
|
||||
when (nEvents > 0) do
|
||||
let evPtr' = castPtr evPtr :: Ptr ()
|
||||
[C.exp| void { ImGui_ImplSDL2_ProcessEvent((SDL_Event*) $(void* evPtr')) } |]
|
||||
|
||||
pollEvent
|
57
src/DearImGui/SDL/OpenGL.hs
Normal file
57
src/DearImGui/SDL/OpenGL.hs
Normal file
@ -0,0 +1,57 @@
|
||||
{-# LANGUAGE BlockArguments #-}
|
||||
{-# LANGUAGE FlexibleContexts #-}
|
||||
{-# LANGUAGE NamedFieldPuns #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# LANGUAGE PatternSynonyms #-}
|
||||
{-# LANGUAGE QuasiQuotes #-}
|
||||
{-# LANGUAGE TemplateHaskell #-}
|
||||
|
||||
{-|
|
||||
Module: DearImGUI.SDL.OpenGL
|
||||
|
||||
Initialising the OpenGL backend for Dear ImGui using SDL2.
|
||||
-}
|
||||
|
||||
module DearImGui.SDL.OpenGL
|
||||
( sdl2InitForOpenGL )
|
||||
where
|
||||
|
||||
-- base
|
||||
import Foreign.Ptr
|
||||
( Ptr )
|
||||
import Unsafe.Coerce
|
||||
( unsafeCoerce )
|
||||
|
||||
-- inline-c
|
||||
import qualified Language.C.Inline as C
|
||||
|
||||
-- inline-c-cpp
|
||||
import qualified Language.C.Inline.Cpp as Cpp
|
||||
|
||||
-- sdl2
|
||||
import SDL
|
||||
( GLContext )
|
||||
import SDL.Internal.Types
|
||||
( Window(..) )
|
||||
|
||||
-- transformers
|
||||
import Control.Monad.IO.Class
|
||||
( MonadIO, liftIO )
|
||||
|
||||
|
||||
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 @ImGui_ImplSDL2_InitForOpenGL@.
|
||||
sdl2InitForOpenGL :: MonadIO m => Window -> GLContext -> m ()
|
||||
sdl2InitForOpenGL (Window windowPtr) glContext = liftIO do
|
||||
[C.exp| void { ImGui_ImplSDL2_InitForOpenGL((SDL_Window*)$(void* windowPtr), $(void* glContextPtr)); } |]
|
||||
where
|
||||
glContextPtr :: Ptr ()
|
||||
glContextPtr = unsafeCoerce glContext
|
Reference in New Issue
Block a user