{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TemplateHaskell #-}

{-|
Module: DearImGui.GLFW

GLFW specific functions backend for Dear ImGui.

Modules for initialising a backend with GLFW can be found under the corresponding backend,
e.g. "DearImGui.GLFW.OpenGL".
-}

module DearImGui.GLFW (
    -- ** GLFW
    glfwNewFrame
  , glfwShutdown

    -- $callbacks
  , glfwWindowFocusCallback
  , glfwCursorEnterCallback
  , glfwCursorPosCallback
  , glfwMouseButtonCallback
  , glfwScrollCallback
  , glfwKeyCallback
  , glfwCharCallback
  , glfwMonitorCallback
  )
  where

-- base
import Foreign
  ( Ptr, castPtr )
import Foreign.C.Types
  ( CInt, CDouble, CUInt )
import Unsafe.Coerce (unsafeCoerce)

-- bindings-GLFW
import Bindings.GLFW
  ( C'GLFWmonitor, C'GLFWwindow )

-- GLFW-b
import Graphics.UI.GLFW
  ( Monitor, Window )

-- 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 )


C.context (Cpp.cppCtx <> C.bsCtx)
C.include "imgui.h"
C.include "backends/imgui_impl_glfw.h"
Cpp.using "namespace ImGui"


-- | Wraps @ImGui_ImplGlfw_NewFrame@.
glfwNewFrame :: MonadIO m => m ()
glfwNewFrame :: forall (m :: * -> *). MonadIO m => m ()
glfwNewFrame = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { ImGui_ImplGlfw_NewFrame(); } |]

-- $callbacks
-- == GLFW callbacks
-- * When calling Init with @install_callbacks=true@:
--   GLFW callbacks will be installed for you.
--   They will call user's previously installed callbacks, if any.
-- * When calling Init with @install_callbacks=false@:
--   GLFW callbacks won't be installed.
--   You will need to call those function yourself from your own GLFW callbacks.

-- | Wraps @ImGui_ImplGlfw_Shutdown@.
glfwShutdown :: MonadIO m => m ()
glfwShutdown :: forall (m :: * -> *). MonadIO m => m ()
glfwShutdown = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { ImGui_ImplGlfw_Shutdown(); } |]

glfwWindowFocusCallback :: MonadIO m => Window -> CInt -> m ()
glfwWindowFocusCallback :: forall (m :: * -> *). MonadIO m => Window -> CInt -> m ()
glfwWindowFocusCallback Window
window CInt
focused = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void {
    ImGui_ImplGlfw_WindowFocusCallback(
      static_cast<GLFWwindow *>(
        $(void * windowPtr)
      ),
      $(int focused)
    );
  } |]
  where
    windowPtr :: Ptr b
windowPtr = Ptr C'GLFWwindow -> Ptr b
forall a b. Ptr a -> Ptr b
castPtr (Ptr C'GLFWwindow -> Ptr b) -> Ptr C'GLFWwindow -> Ptr b
forall a b. (a -> b) -> a -> b
$ Window -> Ptr C'GLFWwindow
unWindow Window
window

glfwCursorEnterCallback :: MonadIO m => Window -> CInt -> m ()
glfwCursorEnterCallback :: forall (m :: * -> *). MonadIO m => Window -> CInt -> m ()
glfwCursorEnterCallback Window
window CInt
entered = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void {
    ImGui_ImplGlfw_CursorEnterCallback(
      static_cast<GLFWwindow *>(
        $(void * windowPtr)
      ),
      $(int entered)
    );
  } |]
  where
    windowPtr :: Ptr b
windowPtr = Ptr C'GLFWwindow -> Ptr b
forall a b. Ptr a -> Ptr b
castPtr (Ptr C'GLFWwindow -> Ptr b) -> Ptr C'GLFWwindow -> Ptr b
forall a b. (a -> b) -> a -> b
$ Window -> Ptr C'GLFWwindow
unWindow Window
window

glfwCursorPosCallback :: MonadIO m => Window -> CDouble -> CDouble -> m ()
glfwCursorPosCallback :: forall (m :: * -> *).
MonadIO m =>
Window -> CDouble -> CDouble -> m ()
glfwCursorPosCallback Window
window CDouble
x CDouble
y = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void {
    ImGui_ImplGlfw_CursorPosCallback(
      static_cast<GLFWwindow *>(
        $(void * windowPtr)
      ),
      $(double x),
      $(double y)
    );
  } |]
  where
    windowPtr :: Ptr b
windowPtr = Ptr C'GLFWwindow -> Ptr b
forall a b. Ptr a -> Ptr b
castPtr (Ptr C'GLFWwindow -> Ptr b) -> Ptr C'GLFWwindow -> Ptr b
forall a b. (a -> b) -> a -> b
$ Window -> Ptr C'GLFWwindow
unWindow Window
window

glfwMouseButtonCallback :: MonadIO m => Window -> CInt -> CInt -> CInt -> m ()
glfwMouseButtonCallback :: forall (m :: * -> *).
MonadIO m =>
Window -> CInt -> CInt -> CInt -> m ()
glfwMouseButtonCallback Window
window CInt
button CInt
action CInt
mods = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void {
    ImGui_ImplGlfw_MouseButtonCallback(
      static_cast<GLFWwindow *>(
        $(void * windowPtr)
      ),
      $(int button),
      $(int action),
      $(int mods)
    );
  } |]
  where
    windowPtr :: Ptr b
windowPtr = Ptr C'GLFWwindow -> Ptr b
forall a b. Ptr a -> Ptr b
castPtr (Ptr C'GLFWwindow -> Ptr b) -> Ptr C'GLFWwindow -> Ptr b
forall a b. (a -> b) -> a -> b
$ Window -> Ptr C'GLFWwindow
unWindow Window
window

glfwScrollCallback :: MonadIO m => Window -> CDouble -> CDouble -> m ()
glfwScrollCallback :: forall (m :: * -> *).
MonadIO m =>
Window -> CDouble -> CDouble -> m ()
glfwScrollCallback Window
window CDouble
xoffset CDouble
yoffset = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void {
    ImGui_ImplGlfw_ScrollCallback(
      static_cast<GLFWwindow *>(
        $(void * windowPtr)
      ),
      $(double xoffset),
      $(double yoffset)
    );
  } |]
  where
    windowPtr :: Ptr b
windowPtr = Ptr C'GLFWwindow -> Ptr b
forall a b. Ptr a -> Ptr b
castPtr (Ptr C'GLFWwindow -> Ptr b) -> Ptr C'GLFWwindow -> Ptr b
forall a b. (a -> b) -> a -> b
$ Window -> Ptr C'GLFWwindow
unWindow Window
window

glfwKeyCallback :: MonadIO m => Window -> CInt -> CInt -> CInt -> CInt -> m ()
glfwKeyCallback :: forall (m :: * -> *).
MonadIO m =>
Window -> CInt -> CInt -> CInt -> CInt -> m ()
glfwKeyCallback Window
window CInt
key CInt
scancode CInt
action CInt
mods = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void {
    ImGui_ImplGlfw_KeyCallback(
      static_cast<GLFWwindow *>(
        $(void * windowPtr)
      ),
      $(int key),
      $(int scancode),
      $(int action),
      $(int mods)
    );
  } |]
  where
    windowPtr :: Ptr b
windowPtr = Ptr C'GLFWwindow -> Ptr b
forall a b. Ptr a -> Ptr b
castPtr (Ptr C'GLFWwindow -> Ptr b) -> Ptr C'GLFWwindow -> Ptr b
forall a b. (a -> b) -> a -> b
$ Window -> Ptr C'GLFWwindow
unWindow Window
window

glfwCharCallback :: MonadIO m => Window -> CUInt -> m ()
glfwCharCallback :: forall (m :: * -> *). MonadIO m => Window -> CUInt -> m ()
glfwCharCallback Window
window CUInt
c = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void {
    ImGui_ImplGlfw_CharCallback(
      static_cast<GLFWwindow *>(
        $(void * windowPtr)
      ),
      $(unsigned int c)
    );
  } |]
  where
    windowPtr :: Ptr b
windowPtr = Ptr C'GLFWwindow -> Ptr b
forall a b. Ptr a -> Ptr b
castPtr (Ptr C'GLFWwindow -> Ptr b) -> Ptr C'GLFWwindow -> Ptr b
forall a b. (a -> b) -> a -> b
$ Window -> Ptr C'GLFWwindow
unWindow Window
window

glfwMonitorCallback :: MonadIO m => Monitor -> CInt -> m ()
glfwMonitorCallback :: forall (m :: * -> *). MonadIO m => Monitor -> CInt -> m ()
glfwMonitorCallback Monitor
monitor CInt
event = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void {
    ImGui_ImplGlfw_MonitorCallback(
      static_cast<GLFWmonitor *>(
        $(void * monitorPtr)
      ),
      $(int event)
    );
  } |]
  where
    monitorPtr :: Ptr b
monitorPtr = Ptr C'GLFWmonitor -> Ptr b
forall a b. Ptr a -> Ptr b
castPtr (Ptr C'GLFWmonitor -> Ptr b) -> Ptr C'GLFWmonitor -> Ptr b
forall a b. (a -> b) -> a -> b
$ Monitor -> Ptr C'GLFWmonitor
unMonitor Monitor
monitor

-- | Strip the unpublished newtype wrapper.
unWindow :: Window -> Ptr C'GLFWwindow
unWindow :: Window -> Ptr C'GLFWwindow
unWindow = Window -> Ptr C'GLFWwindow
forall a b. a -> b
unsafeCoerce

-- | Strip the unpublished newtype wrapper.
unMonitor :: Monitor -> Ptr C'GLFWmonitor
unMonitor :: Monitor -> Ptr C'GLFWmonitor
unMonitor = Monitor -> Ptr C'GLFWmonitor
forall a b. a -> b
unsafeCoerce