{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE ViewPatterns #-}

{-|
Module: DearImGui

Main ImGui module, exporting the functions to create a GUI.
-}

module DearImGui.Raw
  ( -- * Context Creation and Access
    Context(..)
  , createContext
  , destroyContext
  , getCurrentContext
  , setCurrentContext

    -- * Main
  , newFrame
  , endFrame
  , render
  , DrawData(..)
  , getDrawData
  , checkVersion

    -- * Demo, Debug, Information
  , showDemoWindow
  , showMetricsWindow
  , showAboutWindow
  , showUserGuide
  , getVersion

    -- * Styles
  , styleColorsDark
  , styleColorsLight
  , styleColorsClassic

    -- * Windows
  , begin
  , end

    -- ** Utilities

  , getWindowDrawList
  , getWindowPos
  , getWindowSize
  , getWindowWidth
  , getWindowHeight

    -- ** Manipulation

  , setNextWindowPos
  , setNextWindowSize
  , setNextWindowFullscreen
  , setNextWindowContentSize
  , setNextWindowSizeConstraints
  , setNextWindowCollapsed
  , setNextWindowBgAlpha

    -- ** Child Windows
  , beginChild
  , beginChildContext
  , endChild

    -- * Parameter stacks
  , pushStyleColor
  , popStyleColor
  , pushStyleVar
  , popStyleVar

    -- * Cursor/Layout
  , separator
  , sameLine
  , newLine
  , spacing
  , dummy
  , indent
  , unindent
  , setNextItemWidth
  , pushItemWidth
  , popItemWidth
  , beginGroup
  , endGroup
  , setCursorPos
  , getCursorScreenPos
  , alignTextToFramePadding

    -- * Widgets
    -- ** Text
  , textUnformatted
  , textColored
  , textDisabled
  , textWrapped
  , labelText
  , bulletText

    -- ** Main
  , button
  , smallButton
  , invisibleButton
  , arrowButton
  , image
  , imageButton
  , checkbox
  , progressBar
  , bullet

    -- ** Combo Box
  , beginCombo
  , endCombo
  , combo

    -- ** Drag Sliders
  , dragFloat
  , dragFloat2
  , dragFloat3
  , dragFloat4
  , dragFloatRange2
  , dragInt
  , dragInt2
  , dragInt3
  , dragInt4
  , dragIntRange2
  , dragScalar
  , dragScalarN

    -- ** Slider
  , sliderFloat
  , sliderFloat2
  , sliderFloat3
  , sliderFloat4
  , sliderAngle
  , sliderInt
  , sliderInt2
  , sliderInt3
  , sliderInt4
  , sliderScalar
  , sliderScalarN
  , vSliderFloat
  , vSliderInt
  , vSliderScalar

    -- ** Text Input
  , inputText
  , inputTextMultiline
  , inputTextWithHint

    -- * Color Editor/Picker
  , colorPicker3
  , colorButton

    -- * Tables
  , beginTable
  , endTable
  , tableNextRow
  , tableNextColumn
  , tableSetColumnIndex

  , tableSetupColumn
  , tableSetupScrollFreeze
  , tableHeadersRow
  , tableHeader

  , tableGetSortSpecs
  , tableClearSortSpecsDirty

  , tableGetColumnCount
  , tableGetColumnIndex
  , tableGetRowIndex
  , tableGetColumnName
  , tableGetColumnFlags
  , tableSetColumnEnabled
  , tableSetBgColor

    -- * Trees
  , treeNode
  , treePush
  , treePop

    -- ** Selectables
  , selectable

    -- ** List Boxes
  , listBox

    -- * Data Plotting
  , plotHistogram

    -- ** Menus
  , beginMenuBar
  , endMenuBar
  , beginMainMenuBar
  , endMainMenuBar
  , beginMenu
  , endMenu
  , menuItem

    -- ** Tabs, tab bar
  , beginTabBar
  , endTabBar
  , beginTabItem
  , endTabItem
  , tabItemButton
  , setTabItemClosed

    -- * Tooltips
  , beginTooltip
  , endTooltip

    -- * Popups/Modals
  , beginPopup
  , beginPopupModal
  , endPopup
  , openPopup
  , openPopupOnItemClick
  , closeCurrentPopup
  , beginPopupContextItem
  , beginPopupContextWindow
  , beginPopupContextVoid
  , isPopupOpen

    -- * ID stack/scopes
  , pushIDInt
  , pushIDPtr
  , pushIDStr
  , pushIDStrLen
  , popID

    -- * Item/Widgets Utilities
  , isItemHovered
  , wantCaptureMouse
  , wantCaptureKeyboard

    -- * Utilities

    -- ** Miscellaneous
  , getBackgroundDrawList
  , getForegroundDrawList
  , imCol32

    -- * Types
  , module DearImGui.Enums
  , module DearImGui.Structs
  )
  where

-- base
import Control.Monad.IO.Class
  ( MonadIO, liftIO )
import Foreign
import Foreign.C
import System.IO.Unsafe
  ( unsafePerformIO )

-- dear-imgui
import DearImGui.Context
  ( imguiContext )
import DearImGui.Enums
import DearImGui.Structs
import DearImGui.Raw.DrawList (DrawList(..))

-- inline-c
import qualified Language.C.Inline as C

-- inline-c-cpp
import qualified Language.C.Inline.Cpp as Cpp

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


-- | Wraps @ImGuiContext*@.
newtype Context = Context (Ptr ImGuiContext)


-- | Wraps @ImGui::CreateContext()@.
createContext :: (MonadIO m) => m Context
createContext :: forall (m :: * -> *). MonadIO m => m Context
createContext = IO Context -> m Context
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  Ptr ImGuiContext -> Context
Context (Ptr ImGuiContext -> Context)
-> IO (Ptr ImGuiContext) -> IO Context
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| ImGuiContext* { CreateContext() } |]


-- | Wraps @ImGui::DestroyContext()@.
destroyContext :: (MonadIO m) => Context -> m ()
destroyContext :: forall (m :: * -> *). MonadIO m => Context -> m ()
destroyContext (Context Ptr ImGuiContext
contextPtr) = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { DestroyContext($(ImGuiContext* contextPtr)); } |]

-- | Wraps @ImGui::GetCurrentContext()@.
getCurrentContext :: MonadIO m => m Context
getCurrentContext :: forall (m :: * -> *). MonadIO m => m Context
getCurrentContext = IO Context -> m Context
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  Ptr ImGuiContext -> Context
Context (Ptr ImGuiContext -> Context)
-> IO (Ptr ImGuiContext) -> IO Context
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| ImGuiContext* { GetCurrentContext() } |]


-- | Wraps @ImGui::SetCurrentContext()@.
setCurrentContext :: MonadIO m => Context -> m ()
setCurrentContext :: forall (m :: * -> *). MonadIO m => Context -> m ()
setCurrentContext (Context Ptr ImGuiContext
contextPtr) = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { SetCurrentContext($(ImGuiContext* contextPtr)) } |]


-- | Start a new Dear ImGui frame, you can submit any command from this point
-- until 'render'/'endFrame'.
--
-- Wraps @ImGui::NewFrame()@.
newFrame :: (MonadIO m) => m ()
newFrame :: forall (m :: * -> *). MonadIO m => m ()
newFrame = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { NewFrame(); } |]


-- | 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!
endFrame :: (MonadIO m) => m ()
endFrame :: forall (m :: * -> *). MonadIO m => m ()
endFrame = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { EndFrame(); } |]


-- | Ends the Dear ImGui frame, finalize the draw data. You can then get call
-- 'getDrawData'.
render :: (MonadIO m) => m ()
render :: forall (m :: * -> *). MonadIO m => m ()
render = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { Render(); } |]


-- | Wraps @ImDrawData*@.
newtype DrawData = DrawData (Ptr ())


-- | Valid after 'render' and until the next call to 'newFrame'. This is what
-- you have to render.
getDrawData :: (MonadIO m) => m DrawData
getDrawData :: forall (m :: * -> *). MonadIO m => m DrawData
getDrawData = IO DrawData -> m DrawData
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  Ptr () -> DrawData
DrawData (Ptr () -> DrawData) -> IO (Ptr ()) -> IO DrawData
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| void* { GetDrawData() } |]


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


-- | Create demo window. Demonstrate most ImGui features. Call this to learn
-- about the library! Try to make it always available in your application!
showDemoWindow :: (MonadIO m) => m ()
showDemoWindow :: forall (m :: * -> *). MonadIO m => m ()
showDemoWindow = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { ShowDemoWindow(); } |]


-- | Create Metrics/Debugger window. Display Dear ImGui internals: windows, draw
-- commands, various internal state, etc.
showMetricsWindow :: (MonadIO m) => m ()
showMetricsWindow :: forall (m :: * -> *). MonadIO m => m ()
showMetricsWindow = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { ShowMetricsWindow(); } |]


-- | Create About window. display Dear ImGui version, credits and build/system
-- information.
showAboutWindow :: (MonadIO m) => m ()
showAboutWindow :: forall (m :: * -> *). MonadIO m => m ()
showAboutWindow = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { ShowAboutWindow(); } |]


-- | Add basic help/info block (not a window): how to manipulate ImGui as a
-- end-user (mouse/keyboard controls).
showUserGuide :: (MonadIO m) => m ()
showUserGuide :: forall (m :: * -> *). MonadIO m => m ()
showUserGuide = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { ShowUserGuide() } |]


-- | Get the compiled version string e.g. "1.80 WIP" (essentially the value for
-- @IMGUI_VERSION@ from the compiled version of @imgui.cpp@).
getVersion :: (MonadIO m) => m CString
getVersion :: forall (m :: * -> *). MonadIO m => m CString
getVersion = IO CString -> m CString
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| const char* { GetVersion() } |]


-- | New, recommended style (default).
--
-- Wraps @ImGui::StyleColorsDark()@.
styleColorsDark :: (MonadIO m) => m ()
styleColorsDark :: forall (m :: * -> *). MonadIO m => m ()
styleColorsDark = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { StyleColorsDark(); } |]


-- | Best used with borders and a custom, thicker font.
--
-- Wraps @ImGui::StyleColorsLight()@.
styleColorsLight :: (MonadIO m) => m ()
styleColorsLight :: forall (m :: * -> *). MonadIO m => m ()
styleColorsLight = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { StyleColorsLight(); } |]


-- | Classic ImGui style.
--
-- Wraps @ImGui::StyleColorsClasic()@.
styleColorsClassic :: (MonadIO m) => m ()
styleColorsClassic :: forall (m :: * -> *). MonadIO m => m ()
styleColorsClassic = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { StyleColorsClassic(); } |]


-- | 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()@.
--
-- Passing non-null @Ptr CBool@ shows a window-closing widget in the upper-right corner of the window,
-- wich clicking will set the boolean to false when clicked.
begin :: (MonadIO m) => CString -> Maybe (Ptr CBool) -> Maybe (ImGuiWindowFlags) -> m Bool
begin :: forall (m :: * -> *).
MonadIO m =>
CString -> Maybe (Ptr CBool) -> Maybe ImGuiWindowFlags -> m Bool
begin CString
namePtr (Just Ptr CBool
openPtr) (Just ImGuiWindowFlags
flags) = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (CBool
0 CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/=) (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| bool { Begin($(char* namePtr), $(bool* openPtr), $(ImGuiWindowFlags flags)) } |]
begin CString
namePtr (Just Ptr CBool
openPtr) Maybe ImGuiWindowFlags
Nothing = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (CBool
0 CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/=) (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| bool { Begin($(char* namePtr), $(bool* openPtr)) } |]
begin CString
namePtr Maybe (Ptr CBool)
Nothing Maybe ImGuiWindowFlags
Nothing = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (CBool
0 CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/=) (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| bool { Begin($(char* namePtr)) } |]
begin CString
_ Maybe (Ptr CBool)
Nothing Maybe ImGuiWindowFlags
_ = [Char] -> m Bool
forall a. HasCallStack => [Char] -> a
error [Char]
"C++ default argument restriction."

-- | Pop window from the stack.
--
-- Wraps @ImGui::End()@.
end :: (MonadIO m) => m ()
end :: forall (m :: * -> *). MonadIO m => m ()
end = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { End(); } |]


-- | Begin a self-contained independent scrolling/clipping regions within a host window.
--
-- Child windows can embed their own child.
--
-- For each independent axis of @size@:
--   * ==0.0f: use remaining host window size
--   * >0.0f: fixed size
--   * <0.0f: use remaining window size minus abs(size)
--
-- Each axis can use a different mode, e.g. @ImVec2 0 400@.
--
-- @BeginChild()@ 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 `endChild` for each `beginChild` call, regardless of its return value.
--
-- Wraps @ImGui::BeginChild()@.
beginChild :: (MonadIO m) => CString -> Ptr ImVec2 -> CBool -> ImGuiWindowFlags -> m Bool
beginChild :: forall (m :: * -> *).
MonadIO m =>
CString -> Ptr ImVec2 -> CBool -> ImGuiWindowFlags -> m Bool
beginChild CString
namePtr Ptr ImVec2
sizePtr CBool
border ImGuiWindowFlags
flags = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (CBool
0 CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/=) (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp|
    bool {
      BeginChild(
        $(char* namePtr),
        *$(ImVec2* sizePtr),
        $(bool border),
        $(ImGuiWindowFlags flags)
      )
    }
  |]

-- | Switch context to another child window by its ID
--
-- Wraps @ImGui::BeginChild()@.
beginChildContext :: (MonadIO m) => CString -> m Bool
beginChildContext :: forall (m :: * -> *). MonadIO m => CString -> m Bool
beginChildContext CString
namePtr = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (CBool
0 CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/=) (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp|
    bool {
      BeginChild(
        $(char* namePtr)
      )
    }
  |]

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


-- | Separator, generally horizontal. inside a menu bar or in horizontal layout
-- mode, this becomes a vertical separator.
--
-- Wraps @ImGui::Separator()@
separator :: (MonadIO m) => m ()
separator :: forall (m :: * -> *). MonadIO m => m ()
separator = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { Separator(); } |]


-- | Call between widgets or groups to layout them horizontally.
--
-- Wraps @ImGui::SameLine@.
sameLine :: (MonadIO m) => m ()
sameLine :: forall (m :: * -> *). MonadIO m => m ()
sameLine = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { SameLine(); } |]

-- | Raw text without formatting.
--
-- Roughly equivalent to Text("%s", text) but:
--   A) doesn't require null terminated string if 'text_end' is specified,
--   B) it's faster, no memory copy is done, no buffer size limits, recommended for long chunks of text.
--
-- Wraps @ImGui::TextUnformatted()@.
textUnformatted :: (MonadIO m) => CString -> Maybe CString -> m ()
textUnformatted :: forall (m :: * -> *). MonadIO m => CString -> Maybe CString -> m ()
textUnformatted CString
textPtr (Just CString
textEndPtr) = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { TextUnformatted($(char* textPtr), $(char* textEndPtr)) } |]
textUnformatted CString
textPtr Maybe CString
Nothing = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { TextUnformatted($(char* textPtr)) } |]

-- | Shortcut for @PushStyleColor(ImGuiCol_Text, col); Text(fmt, ...); PopStyleColor();@.
--
-- XXX: Unlike the original, does not do string formatting.
--
-- Wraps @ImGui::TextColored()@.
textColored :: (MonadIO m) => Ptr ImVec4 -> CString -> m ()
textColored :: forall (m :: * -> *). MonadIO m => Ptr ImVec4 -> CString -> m ()
textColored Ptr ImVec4
colorPtr CString
textPtr = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { TextColored(*$(ImVec4 *colorPtr), "%s", $(char* textPtr)) } |]

-- | Shortcut for @PushStyleColor(ImGuiCol_Text, style.Colors[ImGuiCol_TextDisabled]); Text(fmt, ...); PopStyleColor();@.
--
-- XXX: Unlike the original, does not do string formatting.
--
-- Wraps @ImGui::TextWrapped()@.
textDisabled :: (MonadIO m) => CString -> m ()
textDisabled :: forall (m :: * -> *). MonadIO m => CString -> m ()
textDisabled CString
textPtr = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { TextDisabled("%s", $(char* textPtr)) } |]

-- | Shortcut for @PushTextWrapPos(0.0f); Text(fmt, ...); PopTextWrapPos();@.
--
-- Note that this won't work on an auto-resizing window if there's no other widgets to extend the window width,
-- you may need to set a size using 'setNextWindowSize'.
--
-- XXX: Unlike the original, does not do string formatting.
--
-- Wraps @ImGui::TextWrapped()@.
textWrapped :: (MonadIO m) => CString -> m ()
textWrapped :: forall (m :: * -> *). MonadIO m => CString -> m ()
textWrapped CString
textPtr = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { TextWrapped("%s", $(char* textPtr)) } |]

-- | Label+text combo aligned to other label+value widgets.
--
-- XXX: Unlike the original, does not do string formatting.
--
-- Wraps @ImGui::LabelText()@.
labelText :: (MonadIO m) => CString -> CString -> m ()
labelText :: forall (m :: * -> *). MonadIO m => CString -> CString -> m ()
labelText CString
labelPtr CString
textPtr = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { LabelText($(char* labelPtr), "%s", $(char* textPtr)) } |]

-- | Text with a little bullet aligned to the typical tree node.
--
-- XXX: Unlike the original, does not do string formatting.
--
-- Wraps @ImGui::BulletText()@.
bulletText :: (MonadIO m) => CString -> m ()
bulletText :: forall (m :: * -> *). MonadIO m => CString -> m ()
bulletText CString
textPtr = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { BulletText("%s", $(char* textPtr)) } |]

-- | A button. Returns 'True' when clicked.
--
-- Wraps @ImGui::Button()@.
button :: (MonadIO m) => CString -> m Bool
button :: forall (m :: * -> *). MonadIO m => CString -> m Bool
button CString
labelPtr = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (CBool
0 CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/=) (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| bool { Button($(char* labelPtr)) } |]


-- | Button with @FramePadding=(0,0)@ to easily embed within text.
--
-- Wraps @ImGui::SmallButton()@.
smallButton :: (MonadIO m) => CString -> m Bool
smallButton :: forall (m :: * -> *). MonadIO m => CString -> m Bool
smallButton CString
labelPtr = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (CBool
0 CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/=) (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| bool { SmallButton($(char* labelPtr)) } |]


-- | Flexible button behavior without the visuals.
--
-- Frequently useful to build custom behaviors using the public api
-- (along with IsItemActive, IsItemHovered, etc).
--
-- Wraps @ImGui::InvisibleButton()@.
invisibleButton :: (MonadIO m) => CString -> Ptr ImVec2 -> ImGuiButtonFlags -> m Bool
invisibleButton :: forall (m :: * -> *).
MonadIO m =>
CString -> Ptr ImVec2 -> ImGuiButtonFlags -> m Bool
invisibleButton CString
labelPtr Ptr ImVec2
size ImGuiButtonFlags
flags = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (CBool
0 CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/=) (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp|
    bool {
      InvisibleButton(
        $(char* labelPtr),
        *$(ImVec2* size),
        $(ImGuiButtonFlags flags)
      )
    }
  |]

-- | Square button with an arrow shape.
--
-- Wraps @ImGui::ArrowButton()@.
arrowButton :: (MonadIO m) => CString -> ImGuiDir -> m Bool
arrowButton :: forall (m :: * -> *). MonadIO m => CString -> ImGuiDir -> m Bool
arrowButton CString
strIdPtr ImGuiDir
dir = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (CBool
0 CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/=) (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| bool { ArrowButton($(char* strIdPtr), $(ImGuiDir dir)) } |]


-- | Image Area to draw a texture.
--
-- For OpenGL: The @userTextureIDPtr@ points to the texture memory (eg. @0x0000000000000001@)
--
-- See @examples/sdl/Image.hs@ for the whole process.
--
-- Wraps @ImGui::Image()@.
image :: (MonadIO m) => Ptr () -> Ptr ImVec2 -> Ptr ImVec2 -> Ptr ImVec2 -> Ptr ImVec4 -> Ptr ImVec4 -> m ()
image :: forall (m :: * -> *).
MonadIO m =>
Ptr ()
-> Ptr ImVec2
-> Ptr ImVec2
-> Ptr ImVec2
-> Ptr ImVec4
-> Ptr ImVec4
-> m ()
image Ptr ()
userTextureIDPtr Ptr ImVec2
sizePtr Ptr ImVec2
uv0Ptr Ptr ImVec2
uv1Ptr Ptr ImVec4
tintColPtr Ptr ImVec4
borderColPtr = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp|
    void {
      Image(
        $(void* userTextureIDPtr),
        *$(ImVec2* sizePtr),
        *$(ImVec2* uv0Ptr),
        *$(ImVec2* uv1Ptr),
        *$(ImVec4* tintColPtr),
        *$(ImVec4* borderColPtr)
      )
    }
  |]

-- | Clickable Image Area.
--
-- Negative @frame_padding@ uses default frame padding settings. Set to 0 for no padding.
--
-- Wraps @ImGui::ImageButton()@.
imageButton :: (MonadIO m) => Ptr () -> Ptr ImVec2 -> Ptr ImVec2 -> Ptr ImVec2 -> CInt -> Ptr ImVec4 -> Ptr ImVec4 -> m Bool
imageButton :: forall (m :: * -> *).
MonadIO m =>
Ptr ()
-> Ptr ImVec2
-> Ptr ImVec2
-> Ptr ImVec2
-> CInt
-> Ptr ImVec4
-> Ptr ImVec4
-> m Bool
imageButton Ptr ()
userTextureIDPtr Ptr ImVec2
sizePtr Ptr ImVec2
uv0Ptr Ptr ImVec2
uv1Ptr CInt
framePadding Ptr ImVec4
bgColPtr Ptr ImVec4
tintColPtr = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (CBool
0 CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/=) (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp|
    bool {
      ImageButton(
        $(void* userTextureIDPtr),
        *$(ImVec2* sizePtr),
        *$(ImVec2* uv0Ptr),
        *$(ImVec2* uv1Ptr),
        $(int framePadding),
        *$(ImVec4* bgColPtr),
        *$(ImVec4* tintColPtr)
      )
    }
  |]


-- | Wraps @ImGui::Checkbox()@.
checkbox :: (MonadIO m) => CString -> Ptr CBool -> m Bool
checkbox :: forall (m :: * -> *). MonadIO m => CString -> Ptr CBool -> m Bool
checkbox CString
labelPtr Ptr CBool
boolPtr = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (CBool
0 CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/=) (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| bool { Checkbox($(char* labelPtr), $(bool* boolPtr)) } |]


-- TODO: publish ImVec2(-FLT_MIN, 0)
-- | Wraps @ImGui::ProgressBar()@.
progressBar :: (MonadIO m) => CFloat -> CString -> m ()
progressBar :: forall (m :: * -> *). MonadIO m => CFloat -> CString -> m ()
progressBar CFloat
progress CString
overlayPtr = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
    [C.exp| void { ProgressBar($(float progress), ImVec2(-FLT_MIN, 0), $(char* overlayPtr)) } |]


-- | Draw a small circle + keep the cursor on the same line. Advance cursor x
-- position by 'getTreeNodeToLabelSpacing', same distance that 'treeNode' uses.
bullet :: (MonadIO m) => m ()
bullet :: forall (m :: * -> *). MonadIO m => m ()
bullet = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { Bullet() } |]


-- | 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()@.
beginCombo :: (MonadIO m) => CString -> CString -> m Bool
beginCombo :: forall (m :: * -> *). MonadIO m => CString -> CString -> m Bool
beginCombo CString
labelPtr CString
previewValuePtr = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (CBool
0 CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/=) (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| bool { BeginCombo($(char* labelPtr), $(char* previewValuePtr)) } |]


-- | Only call 'endCombo' if 'beginCombo' returns 'True'!
--
-- Wraps @ImGui::EndCombo()@.
endCombo :: (MonadIO m) => m ()
endCombo :: forall (m :: * -> *). MonadIO m => m ()
endCombo = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { EndCombo() } |]


-- | Wraps @ImGui::Combo()@.
combo :: (MonadIO m) => CString -> Ptr CInt -> Ptr CString -> CInt -> m Bool
combo :: forall (m :: * -> *).
MonadIO m =>
CString -> Ptr CInt -> Ptr CString -> CInt -> m Bool
combo CString
labelPtr Ptr CInt
iPtr Ptr CString
itemsPtr CInt
itemsLen = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (CBool
0 CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/=) (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| bool { Combo($(char* labelPtr), $(int* iPtr), $(char** itemsPtr), $(int itemsLen)) }|]


-- | Wraps @ImGui::DragFloat()@
dragFloat :: (MonadIO m) => CString -> Ptr CFloat -> CFloat -> CFloat -> CFloat -> m Bool
dragFloat :: forall (m :: * -> *).
MonadIO m =>
CString -> Ptr CFloat -> CFloat -> CFloat -> CFloat -> m Bool
dragFloat CString
descPtr Ptr CFloat
floatPtr CFloat
speed CFloat
minValue CFloat
maxValue = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (CBool
0 CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/=) (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| bool { DragFloat( $(char* descPtr), $(float* floatPtr), $(float speed), $(float minValue), $(float maxValue)) } |]


-- | Wraps @ImGui::DragFloat2()@
dragFloat2 :: (MonadIO m) => CString -> Ptr CFloat -> CFloat -> CFloat -> CFloat -> m Bool
dragFloat2 :: forall (m :: * -> *).
MonadIO m =>
CString -> Ptr CFloat -> CFloat -> CFloat -> CFloat -> m Bool
dragFloat2 CString
descPtr Ptr CFloat
floatPtr CFloat
speed CFloat
minValue CFloat
maxValue = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (CBool
0 CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/=) (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| bool { DragFloat2( $(char* descPtr), $(float* floatPtr), $(float speed), $(float minValue), $(float maxValue)) } |]


-- | Wraps @ImGui::DragFloat3()@
dragFloat3 :: (MonadIO m) => CString -> Ptr CFloat -> CFloat -> CFloat -> CFloat -> m Bool
dragFloat3 :: forall (m :: * -> *).
MonadIO m =>
CString -> Ptr CFloat -> CFloat -> CFloat -> CFloat -> m Bool
dragFloat3 CString
descPtr Ptr CFloat
floatPtr CFloat
speed CFloat
minValue CFloat
maxValue = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (CBool
0 CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/=) (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| bool { DragFloat3( $(char* descPtr), $(float* floatPtr), $(float speed), $(float minValue), $(float maxValue)) } |]


-- | Wraps @ImGui::DragFloat4()@
dragFloat4 :: (MonadIO m) => CString -> Ptr CFloat -> CFloat -> CFloat -> CFloat -> m Bool
dragFloat4 :: forall (m :: * -> *).
MonadIO m =>
CString -> Ptr CFloat -> CFloat -> CFloat -> CFloat -> m Bool
dragFloat4 CString
descPtr Ptr CFloat
floatPtr CFloat
speed CFloat
minValue CFloat
maxValue = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (CBool
0 CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/=) (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| bool { DragFloat4( $(char* descPtr), $(float* floatPtr), $(float speed), $(float minValue), $(float maxValue)) } |]


-- | Wraps @ImGui::DragFloatRange2()@
dragFloatRange2 :: (MonadIO m) => CString -> Ptr CFloat -> Ptr CFloat -> CFloat -> CFloat -> CFloat -> CString -> CString -> ImGuiSliderFlags -> m Bool
dragFloatRange2 :: forall (m :: * -> *).
MonadIO m =>
CString
-> Ptr CFloat
-> Ptr CFloat
-> CFloat
-> CFloat
-> CFloat
-> CString
-> CString
-> ImGuiSliderFlags
-> m Bool
dragFloatRange2 CString
labelPtr Ptr CFloat
vCurrentMin Ptr CFloat
vCurrentMax CFloat
vSpeed CFloat
vMin CFloat
vMax CString
formatMin CString
formatMax ImGuiSliderFlags
flags = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (CBool
0 CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/=) (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| bool {
    DragFloatRange2(
      $(char* labelPtr),
      $(float* vCurrentMin),
      $(float* vCurrentMax),
      $(float vSpeed),
      $(float vMin),
      $(float vMax),
      $(char* formatMin),
      $(char* formatMax),
      $(ImGuiSliderFlags flags)
    )
  } |]


-- | Wraps @ImGui::DragInt()@
dragInt :: (MonadIO m) => CString -> Ptr CInt -> CFloat -> CInt -> CInt -> CString -> ImGuiSliderFlags -> m Bool
dragInt :: forall (m :: * -> *).
MonadIO m =>
CString
-> Ptr CInt
-> CFloat
-> CInt
-> CInt
-> CString
-> ImGuiSliderFlags
-> m Bool
dragInt CString
labelPtr Ptr CInt
vPtr CFloat
vSpeed CInt
vMin CInt
vMax CString
formatPtr ImGuiSliderFlags
flags = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (CBool
0 CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/=) (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| bool {
    DragInt(
      $(char* labelPtr),
      $(int* vPtr),
      $(float vSpeed),
      $(int vMin),
      $(int vMax),
      $(char* formatPtr),
      $(ImGuiSliderFlags flags)
    )
  } |]

-- | Wraps @ImGui::DragInt2()@
dragInt2 :: (MonadIO m) => CString -> Ptr CInt -> CFloat -> CInt -> CInt -> CString -> ImGuiSliderFlags -> m Bool
dragInt2 :: forall (m :: * -> *).
MonadIO m =>
CString
-> Ptr CInt
-> CFloat
-> CInt
-> CInt
-> CString
-> ImGuiSliderFlags
-> m Bool
dragInt2 CString
labelPtr Ptr CInt
vPtr CFloat
vSpeed CInt
vMin CInt
vMax CString
formatPtr ImGuiSliderFlags
flags = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (CBool
0 CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/=) (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| bool {
    DragInt2(
      $(char* labelPtr),
      $(int vPtr[2]),
      $(float vSpeed),
      $(int vMin),
      $(int vMax),
      $(char* formatPtr),
      $(ImGuiSliderFlags flags)
    )
  } |]

-- | Wraps @ImGui::DragInt3()@
dragInt3 :: (MonadIO m) => CString -> Ptr CInt -> CFloat -> CInt -> CInt -> CString -> ImGuiSliderFlags -> m Bool
dragInt3 :: forall (m :: * -> *).
MonadIO m =>
CString
-> Ptr CInt
-> CFloat
-> CInt
-> CInt
-> CString
-> ImGuiSliderFlags
-> m Bool
dragInt3 CString
labelPtr Ptr CInt
vPtr CFloat
vSpeed CInt
vMin CInt
vMax CString
formatPtr ImGuiSliderFlags
flags = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (CBool
0 CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/=) (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| bool {
    DragInt3(
      $(char* labelPtr),
      $(int vPtr[3]),
      $(float vSpeed),
      $(int vMin),
      $(int vMax),
      $(char* formatPtr),
      $(ImGuiSliderFlags flags)
    )
  } |]

-- | Wraps @ImGui::DragInt4()@
dragInt4 :: (MonadIO m) => CString -> Ptr CInt -> CFloat -> CInt -> CInt -> CString -> ImGuiSliderFlags -> m Bool
dragInt4 :: forall (m :: * -> *).
MonadIO m =>
CString
-> Ptr CInt
-> CFloat
-> CInt
-> CInt
-> CString
-> ImGuiSliderFlags
-> m Bool
dragInt4 CString
labelPtr Ptr CInt
vPtr CFloat
vSpeed CInt
vMin CInt
vMax CString
formatPtr ImGuiSliderFlags
flags = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (CBool
0 CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/=) (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| bool {
    DragInt4(
      $(char* labelPtr),
      $(int vPtr[4]),
      $(float vSpeed),
      $(int vMin),
      $(int vMax),
      $(char* formatPtr),
      $(ImGuiSliderFlags flags)
    )
  } |]

-- | Wraps @ImGui::DragFloatRange2()@
dragIntRange2 :: (MonadIO m) => CString -> Ptr CInt -> Ptr CInt -> CFloat -> CInt -> CInt -> CString -> CString -> ImGuiSliderFlags -> m Bool
dragIntRange2 :: forall (m :: * -> *).
MonadIO m =>
CString
-> Ptr CInt
-> Ptr CInt
-> CFloat
-> CInt
-> CInt
-> CString
-> CString
-> ImGuiSliderFlags
-> m Bool
dragIntRange2 CString
labelPtr Ptr CInt
vCurrentMin Ptr CInt
vCurrentMax CFloat
vSpeed CInt
vMin CInt
vMax CString
formatMin CString
formatMax ImGuiSliderFlags
flags = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (CBool
0 CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/=) (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| bool {
    DragIntRange2(
      $(char* labelPtr),
      $(int* vCurrentMin),
      $(int* vCurrentMax),
      $(float vSpeed),
      $(int vMin),
      $(int vMax),
      $(char* formatMin),
      $(char* formatMax),
      $(ImGuiSliderFlags flags)
    )
  } |]

-- | Wraps @ImGui::DragScalar()@
dragScalar :: (MonadIO m) => CString -> ImGuiDataType -> Ptr a -> CFloat -> Ptr a -> Ptr a -> CString -> ImGuiSliderFlags -> m Bool
dragScalar :: forall (m :: * -> *) a.
MonadIO m =>
CString
-> ImGuiDataType
-> Ptr a
-> CFloat
-> Ptr a
-> Ptr a
-> CString
-> ImGuiSliderFlags
-> m Bool
dragScalar CString
labelPtr ImGuiDataType
dataType Ptr a
dataPtr CFloat
vSpeed Ptr a
minPtr Ptr a
maxPtr CString
formatPtr ImGuiSliderFlags
flags = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (CBool
0 CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/=) (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| bool {
    DragScalar(
      $(char* labelPtr),
      $(ImGuiDataType dataType),
      $(void* dataPtr_),
      $(float vSpeed),
      $(void* minPtr_),
      $(void* maxPtr_),
      $(char* formatPtr),
      $(ImGuiSliderFlags flags)
    )
  } |]
  where
    dataPtr_ :: Ptr b
dataPtr_ = Ptr a -> Ptr b
forall a b. Ptr a -> Ptr b
castPtr Ptr a
dataPtr
    minPtr_ :: Ptr b
minPtr_ = Ptr a -> Ptr b
forall a b. Ptr a -> Ptr b
castPtr Ptr a
minPtr
    maxPtr_ :: Ptr b
maxPtr_ = Ptr a -> Ptr b
forall a b. Ptr a -> Ptr b
castPtr Ptr a
maxPtr

-- | Wraps @ImGui::DragScalarN()@
dragScalarN :: (MonadIO m) => CString -> ImGuiDataType -> Ptr a -> CInt -> CFloat -> Ptr a -> Ptr a -> CString -> ImGuiSliderFlags -> m Bool
dragScalarN :: forall (m :: * -> *) a.
MonadIO m =>
CString
-> ImGuiDataType
-> Ptr a
-> CInt
-> CFloat
-> Ptr a
-> Ptr a
-> CString
-> ImGuiSliderFlags
-> m Bool
dragScalarN CString
labelPtr ImGuiDataType
dataType Ptr a
dataPtr CInt
components CFloat
vSpeed Ptr a
minPtr Ptr a
maxPtr CString
formatPtr ImGuiSliderFlags
flags = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (CBool
0 CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/=) (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| bool {
    DragScalarN(
      $(char* labelPtr),
      $(ImGuiDataType dataType),
      $(void* dataPtr_),
      $(int components),
      $(float vSpeed),
      $(void* minPtr_),
      $(void* maxPtr_),
      $(char* formatPtr),
      $(ImGuiSliderFlags flags)
    )
  } |]
  where
    dataPtr_ :: Ptr b
dataPtr_ = Ptr a -> Ptr b
forall a b. Ptr a -> Ptr b
castPtr Ptr a
dataPtr
    minPtr_ :: Ptr b
minPtr_ = Ptr a -> Ptr b
forall a b. Ptr a -> Ptr b
castPtr Ptr a
minPtr
    maxPtr_ :: Ptr b
maxPtr_ = Ptr a -> Ptr b
forall a b. Ptr a -> Ptr b
castPtr Ptr a
maxPtr

-- | Wraps @ImGui::SliderFloat()@
sliderFloat :: (MonadIO m) => CString -> Ptr CFloat -> CFloat -> CFloat -> m Bool
sliderFloat :: forall (m :: * -> *).
MonadIO m =>
CString -> Ptr CFloat -> CFloat -> CFloat -> m Bool
sliderFloat CString
descPtr Ptr CFloat
floatPtr CFloat
minValue CFloat
maxValue = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (CBool
0 CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/=) (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| bool { SliderFloat( $(char* descPtr), $(float* floatPtr), $(float minValue), $(float maxValue)) } |]


-- | Wraps @ImGui::SliderFloat2()@
sliderFloat2 :: (MonadIO m) => CString -> Ptr CFloat -> CFloat -> CFloat -> m Bool
sliderFloat2 :: forall (m :: * -> *).
MonadIO m =>
CString -> Ptr CFloat -> CFloat -> CFloat -> m Bool
sliderFloat2 CString
descPtr Ptr CFloat
floatPtr CFloat
minValue CFloat
maxValue = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (CBool
0 CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/=) (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| bool { SliderFloat2( $(char* descPtr), $(float* floatPtr), $(float minValue), $(float maxValue)) } |]


-- | Wraps @ImGui::SliderFloat3()@
sliderFloat3 :: (MonadIO m) => CString -> Ptr CFloat -> CFloat -> CFloat -> m Bool
sliderFloat3 :: forall (m :: * -> *).
MonadIO m =>
CString -> Ptr CFloat -> CFloat -> CFloat -> m Bool
sliderFloat3 CString
descPtr Ptr CFloat
floatPtr CFloat
minValue CFloat
maxValue = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (CBool
0 CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/=) (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| bool { SliderFloat3( $(char* descPtr), $(float* floatPtr), $(float minValue), $(float maxValue)) } |]


-- | Wraps @ImGui::SliderFloat4()@
sliderFloat4 :: (MonadIO m) => CString -> Ptr CFloat -> CFloat -> CFloat -> m Bool
sliderFloat4 :: forall (m :: * -> *).
MonadIO m =>
CString -> Ptr CFloat -> CFloat -> CFloat -> m Bool
sliderFloat4 CString
descPtr Ptr CFloat
floatPtr CFloat
minValue CFloat
maxValue = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (CBool
0 CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/=) (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| bool { SliderFloat4( $(char* descPtr), $(float* floatPtr), $(float minValue), $(float maxValue)) } |]

-- | Wraps @ImGui::SliderAngle()@
sliderAngle :: (MonadIO m) => CString -> Ptr CFloat -> CFloat -> CFloat -> CString -> ImGuiSliderFlags -> m Bool
sliderAngle :: forall (m :: * -> *).
MonadIO m =>
CString
-> Ptr CFloat
-> CFloat
-> CFloat
-> CString
-> ImGuiSliderFlags
-> m Bool
sliderAngle CString
descPtr Ptr CFloat
valueRadPtr CFloat
degreesMin CFloat
degreesMax CString
format ImGuiSliderFlags
flags = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (CBool
0 CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/=) (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| bool {
    SliderAngle(
      $(char* descPtr),
      $(float* valueRadPtr),
      $(float degreesMin),
      $(float degreesMax),
      $(char* format),
      $(ImGuiSliderFlags flags)
    )
  } |]

-- | Wraps @ImGui::SliderInt()@
sliderInt :: (MonadIO m) => CString -> Ptr CInt -> CInt -> CInt -> CString -> ImGuiSliderFlags -> m Bool
sliderInt :: forall (m :: * -> *).
MonadIO m =>
CString
-> Ptr CInt
-> CInt
-> CInt
-> CString
-> ImGuiSliderFlags
-> m Bool
sliderInt CString
labelPtr Ptr CInt
vPtr CInt
vMin CInt
vMax CString
formatPtr ImGuiSliderFlags
flags = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (CBool
0 CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/=) (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| bool {
    SliderInt(
      $(char* labelPtr),
      $(int* vPtr),
      $(int vMin),
      $(int vMax),
      $(char* formatPtr),
      $(ImGuiSliderFlags flags)
    )
  } |]

-- | Wraps @ImGui::SliderInt2()@
sliderInt2 :: (MonadIO m) => CString -> Ptr CInt -> CInt -> CInt -> CString -> ImGuiSliderFlags -> m Bool
sliderInt2 :: forall (m :: * -> *).
MonadIO m =>
CString
-> Ptr CInt
-> CInt
-> CInt
-> CString
-> ImGuiSliderFlags
-> m Bool
sliderInt2 CString
labelPtr Ptr CInt
vPtr CInt
vMin CInt
vMax CString
formatPtr ImGuiSliderFlags
flags = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (CBool
0 CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/=) (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| bool {
    SliderInt2(
      $(char* labelPtr),
      $(int vPtr[2]),
      $(int vMin),
      $(int vMax),
      $(char* formatPtr),
      $(ImGuiSliderFlags flags)
    )
  } |]

-- | Wraps @ImGui::SliderInt3()@
sliderInt3 :: (MonadIO m) => CString -> Ptr CInt -> CInt -> CInt -> CString -> ImGuiSliderFlags -> m Bool
sliderInt3 :: forall (m :: * -> *).
MonadIO m =>
CString
-> Ptr CInt
-> CInt
-> CInt
-> CString
-> ImGuiSliderFlags
-> m Bool
sliderInt3 CString
labelPtr Ptr CInt
vPtr CInt
vMin CInt
vMax CString
formatPtr ImGuiSliderFlags
flags = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (CBool
0 CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/=) (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| bool {
    SliderInt3(
      $(char* labelPtr),
      $(int vPtr[3]),
      $(int vMin),
      $(int vMax),
      $(char* formatPtr),
      $(ImGuiSliderFlags flags)
    )
  } |]

-- | Wraps @ImGui::SliderInt4()@
sliderInt4 :: (MonadIO m) => CString -> Ptr CInt -> CInt -> CInt -> CString -> ImGuiSliderFlags -> m Bool
sliderInt4 :: forall (m :: * -> *).
MonadIO m =>
CString
-> Ptr CInt
-> CInt
-> CInt
-> CString
-> ImGuiSliderFlags
-> m Bool
sliderInt4 CString
labelPtr Ptr CInt
vPtr CInt
vMin CInt
vMax CString
formatPtr ImGuiSliderFlags
flags = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (CBool
0 CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/=) (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| bool {
    SliderInt4(
      $(char* labelPtr),
      $(int vPtr[4]),
      $(int vMin),
      $(int vMax),
      $(char* formatPtr),
      $(ImGuiSliderFlags flags)
    )
  } |]

-- | Wraps @ImGui::SliderScalar()@
sliderScalar :: (MonadIO m) => CString -> ImGuiDataType -> Ptr a -> Ptr a -> Ptr a -> CString -> ImGuiSliderFlags -> m Bool
sliderScalar :: forall (m :: * -> *) a.
MonadIO m =>
CString
-> ImGuiDataType
-> Ptr a
-> Ptr a
-> Ptr a
-> CString
-> ImGuiSliderFlags
-> m Bool
sliderScalar CString
labelPtr ImGuiDataType
dataType Ptr a
dataPtr Ptr a
minPtr Ptr a
maxPtr CString
formatPtr ImGuiSliderFlags
flags = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (CBool
0 CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/=) (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| bool {
    SliderScalar(
      $(char* labelPtr),
      $(ImGuiDataType dataType),
      $(void* dataPtr_),
      $(void* minPtr_),
      $(void* maxPtr_),
      $(char* formatPtr),
      $(ImGuiSliderFlags flags)
    )
  } |]
  where
    dataPtr_ :: Ptr b
dataPtr_ = Ptr a -> Ptr b
forall a b. Ptr a -> Ptr b
castPtr Ptr a
dataPtr
    minPtr_ :: Ptr b
minPtr_ = Ptr a -> Ptr b
forall a b. Ptr a -> Ptr b
castPtr Ptr a
minPtr
    maxPtr_ :: Ptr b
maxPtr_ = Ptr a -> Ptr b
forall a b. Ptr a -> Ptr b
castPtr Ptr a
maxPtr

-- | Wraps @ImGui::SliderScalarN()@
sliderScalarN :: (MonadIO m) => CString -> ImGuiDataType -> Ptr a -> CInt -> Ptr a -> Ptr a -> CString -> ImGuiSliderFlags -> m Bool
sliderScalarN :: forall (m :: * -> *) a.
MonadIO m =>
CString
-> ImGuiDataType
-> Ptr a
-> CInt
-> Ptr a
-> Ptr a
-> CString
-> ImGuiSliderFlags
-> m Bool
sliderScalarN CString
labelPtr ImGuiDataType
dataType Ptr a
dataPtr CInt
components Ptr a
minPtr Ptr a
maxPtr CString
formatPtr ImGuiSliderFlags
flags = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (CBool
0 CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/=) (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| bool {
    SliderScalarN(
      $(char* labelPtr),
      $(ImGuiDataType dataType),
      $(void* dataPtr_),
      $(int components),
      $(void* minPtr_),
      $(void* maxPtr_),
      $(char* formatPtr),
      $(ImGuiSliderFlags flags)
    )
  } |]
  where
    dataPtr_ :: Ptr b
dataPtr_ = Ptr a -> Ptr b
forall a b. Ptr a -> Ptr b
castPtr Ptr a
dataPtr
    minPtr_ :: Ptr b
minPtr_ = Ptr a -> Ptr b
forall a b. Ptr a -> Ptr b
castPtr Ptr a
minPtr
    maxPtr_ :: Ptr b
maxPtr_ = Ptr a -> Ptr b
forall a b. Ptr a -> Ptr b
castPtr Ptr a
maxPtr

-- | Wraps @ImGui::VSliderFloat()@
vSliderFloat :: (MonadIO m) => CString -> Ptr ImVec2 -> Ptr CFloat -> CFloat -> CFloat -> CString -> ImGuiSliderFlags -> m Bool
vSliderFloat :: forall (m :: * -> *).
MonadIO m =>
CString
-> Ptr ImVec2
-> Ptr CFloat
-> CFloat
-> CFloat
-> CString
-> ImGuiSliderFlags
-> m Bool
vSliderFloat CString
labelPtr Ptr ImVec2
sizePtr Ptr CFloat
vPtr CFloat
vMin CFloat
vMax CString
formatPtr ImGuiSliderFlags
flags = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (CBool
0 CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/=) (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| bool {
    VSliderFloat(
      $(char* labelPtr),
      *$(ImVec2* sizePtr),
      $(float* vPtr),
      $(float vMin),
      $(float vMax),
      $(char* formatPtr),
      $(ImGuiSliderFlags flags)
    )
  } |]

-- | Wraps @ImGui::VSliderFloat()@
vSliderInt :: (MonadIO m) => CString -> Ptr ImVec2 -> Ptr CInt -> CInt -> CInt -> CString -> ImGuiSliderFlags -> m Bool
vSliderInt :: forall (m :: * -> *).
MonadIO m =>
CString
-> Ptr ImVec2
-> Ptr CInt
-> CInt
-> CInt
-> CString
-> ImGuiSliderFlags
-> m Bool
vSliderInt CString
labelPtr Ptr ImVec2
sizePtr Ptr CInt
vPtr CInt
vMin CInt
vMax CString
formatPtr ImGuiSliderFlags
flags = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (CBool
0 CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/=) (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| bool {
    VSliderInt(
      $(char* labelPtr),
      *$(ImVec2* sizePtr),
      $(int* vPtr),
      $(int vMin),
      $(int vMax),
      $(char* formatPtr),
      $(ImGuiSliderFlags flags)
    )
  } |]

-- | Wraps @ImGui::VSliderScalar()@
vSliderScalar :: (MonadIO m) => CString -> Ptr ImVec2 -> ImGuiDataType -> Ptr a -> Ptr a -> Ptr a -> CString -> ImGuiSliderFlags -> m Bool
vSliderScalar :: forall (m :: * -> *) a.
MonadIO m =>
CString
-> Ptr ImVec2
-> ImGuiDataType
-> Ptr a
-> Ptr a
-> Ptr a
-> CString
-> ImGuiSliderFlags
-> m Bool
vSliderScalar CString
labelPtr Ptr ImVec2
sizePtr ImGuiDataType
dataType Ptr a
dataPtr Ptr a
minPtr Ptr a
maxPtr CString
formatPtr ImGuiSliderFlags
flags = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (CBool
0 CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/=) (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| bool {
    VSliderScalar(
      $(char* labelPtr),
      *$(ImVec2* sizePtr),
      $(ImGuiDataType dataType),
      $(void* dataPtr_),
      $(void* minPtr_),
      $(void* maxPtr_),
      $(char* formatPtr),
      $(ImGuiSliderFlags flags)
    )
  } |]
  where
    dataPtr_ :: Ptr b
dataPtr_ = Ptr a -> Ptr b
forall a b. Ptr a -> Ptr b
castPtr Ptr a
dataPtr
    minPtr_ :: Ptr b
minPtr_ = Ptr a -> Ptr b
forall a b. Ptr a -> Ptr b
castPtr Ptr a
minPtr
    maxPtr_ :: Ptr b
maxPtr_ = Ptr a -> Ptr b
forall a b. Ptr a -> Ptr b
castPtr Ptr a
maxPtr


-- | Wraps @ImGui::InputText()@.
inputText :: (MonadIO m) => CString -> CStringLen -> ImGuiInputTextFlags -> m Bool
inputText :: forall (m :: * -> *).
MonadIO m =>
CString -> CStringLen -> ImGuiInputTextFlags -> m Bool
inputText CString
labelPtr (CString
bufPtr, Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral -> CInt
bufSize) ImGuiInputTextFlags
flags = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (CBool
0 CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/= ) (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp|
    bool {
      InputText(
        $(char* labelPtr),
        $(char* bufPtr),
        $(int bufSize),
        $(ImGuiInputTextFlags flags)
      )
    }
  |]

-- | Wraps @ImGui::InputTextMultiline()@.
inputTextMultiline :: (MonadIO m) => CString -> CStringLen -> Ptr ImVec2 -> ImGuiInputTextFlags -> m Bool
inputTextMultiline :: forall (m :: * -> *).
MonadIO m =>
CString
-> CStringLen -> Ptr ImVec2 -> ImGuiInputTextFlags -> m Bool
inputTextMultiline CString
labelPtr (CString
bufPtr, Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral -> CSize
bufSize) Ptr ImVec2
sizePtr ImGuiInputTextFlags
flags = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (CBool
0 CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/= ) (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp|
    bool {
      InputTextMultiline(
        $(char* labelPtr),
        $(char* bufPtr),
        $(size_t bufSize),
        *$(ImVec2* sizePtr),
        $(ImGuiInputTextFlags flags)
      )
    }
  |]

-- | Wraps @ImGui::InputTextWithHint()@.
inputTextWithHint :: (MonadIO m) => CString -> CString -> CStringLen -> ImGuiInputTextFlags -> m Bool
inputTextWithHint :: forall (m :: * -> *).
MonadIO m =>
CString -> CString -> CStringLen -> ImGuiInputTextFlags -> m Bool
inputTextWithHint CString
labelPtr CString
hintPtr (CString
bufPtr, Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral -> CInt
bufSize) ImGuiInputTextFlags
flags = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (CBool
0 CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/= ) (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp|
    bool {
      InputTextWithHint(
        $(char* labelPtr),
        $(char* hintPtr),
        $(char* bufPtr),
        $(int bufSize),
        $(ImGuiInputTextFlags flags)
      )
    }
  |]


-- | Wraps @ImGui::ColorPicker3()@.
colorPicker3 :: (MonadIO m) => CString -> Ptr CFloat -> m Bool
colorPicker3 :: forall (m :: * -> *). MonadIO m => CString -> Ptr CFloat -> m Bool
colorPicker3 CString
descPtr Ptr CFloat
refPtr = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (CBool
0 CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/= ) (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| bool { ColorPicker3( $(char* descPtr), $(float* refPtr) ) } |]


-- | Display a color square/button, hover for details, return true when pressed.
--
-- Wraps @ImGui::ColorButton()@.
colorButton :: (MonadIO m) => CString -> Ptr ImVec4 -> m Bool
colorButton :: forall (m :: * -> *). MonadIO m => CString -> Ptr ImVec4 -> m Bool
colorButton CString
descPtr Ptr ImVec4
refPtr = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (CBool
0 CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/=) (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| bool { ColorButton( $(char* descPtr), *$(ImVec4* refPtr) ) } |]


-- | Wraps @ImGui::BeginTable()@.
beginTable :: MonadIO m => CString -> CInt -> ImGuiTableFlags -> Ptr ImVec2 -> CFloat -> m Bool
beginTable :: forall (m :: * -> *).
MonadIO m =>
CString
-> CInt -> ImGuiTableFlags -> Ptr ImVec2 -> CFloat -> m Bool
beginTable CString
labelPtr CInt
column ImGuiTableFlags
flags Ptr ImVec2
outerSizePtr CFloat
innerWidth = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (CBool
0 CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/=) (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| bool { BeginTable($(char* labelPtr), $(int column), $(ImGuiTableFlags flags), *$(ImVec2* outerSizePtr), $(float innerWidth)) } |]

-- | Only call 'endTable' if 'beginTable' returns true!
--
-- Wraps @ImGui::EndTable()@.
endTable :: MonadIO m => m ()
endTable :: forall (m :: * -> *). MonadIO m => m ()
endTable = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { EndTable() } |]

-- | Wraps @ImGui::TableNextRow()@.
--   append into the first cell of a new row.
tableNextRow :: MonadIO m => ImGuiTableRowFlags -> CFloat -> m ()
tableNextRow :: forall (m :: * -> *).
MonadIO m =>
ImGuiTableRowFlags -> CFloat -> m ()
tableNextRow ImGuiTableRowFlags
flags CFloat
minRowHeight = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { TableNextRow($(ImGuiTableRowFlags flags), $(float minRowHeight)) } |]

-- | Wraps @ImGui::TableNextColumn()@.
--   append into the next column (or first column of next row if currently in
--   last column). Return true when column is visible.
tableNextColumn :: MonadIO m => m Bool
tableNextColumn :: forall (m :: * -> *). MonadIO m => m Bool
tableNextColumn = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (CBool
0 CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/=) (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| bool { TableNextColumn() } |]

-- | Wraps @ImGui::TableSetColumnIndex()@.
--   append into the specified column. Return true when column is visible.
tableSetColumnIndex :: MonadIO m => CInt -> m Bool
tableSetColumnIndex :: forall (m :: * -> *). MonadIO m => CInt -> m Bool
tableSetColumnIndex CInt
column= IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (CBool
0 CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/=) (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| bool { TableSetColumnIndex($(int column)) } |]

-- | Wraps @ImGui::TableSetupColumn()@.
tableSetupColumn :: MonadIO m => CString -> ImGuiTableColumnFlags -> CFloat -> ImGuiID-> m ()
tableSetupColumn :: forall (m :: * -> *).
MonadIO m =>
CString -> ImGuiTableColumnFlags -> CFloat -> ImGuiID -> m ()
tableSetupColumn CString
labelPtr ImGuiTableColumnFlags
flags CFloat
initWidthOrWeight ImGuiID
userId = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { TableSetupColumn($(char* labelPtr), $(ImGuiTableColumnFlags flags), $(float initWidthOrWeight), $(ImGuiID userId)) } |]

-- | Wraps @ImGui::TableSetupScrollFreeze()@.
tableSetupScrollFreeze :: MonadIO m => CInt -> CInt -> m ()
tableSetupScrollFreeze :: forall (m :: * -> *). MonadIO m => CInt -> CInt -> m ()
tableSetupScrollFreeze CInt
cols CInt
rows = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { TableSetupScrollFreeze($(int cols), $(int rows)) } |]

-- | Wraps @ImGui::TableHeadersRow()@.
--   submit all headers cells based on data provided to 'tableSetupColumn'
--   + submit context menu
tableHeadersRow :: MonadIO m => m ()
tableHeadersRow :: forall (m :: * -> *). MonadIO m => m ()
tableHeadersRow = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { TableHeadersRow() } |]

-- | Wraps @ImGui::TableHeader()@.
--   submit one header cell manually (rarely used)
tableHeader :: MonadIO m => CString -> m ()
tableHeader :: forall (m :: * -> *). MonadIO m => CString -> m ()
tableHeader CString
labelPtr = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { TableHeader($(char* labelPtr)) } |]

-- | Wraps @ImGui::TableGetSortSpecs()@.
--   Low-level-Function. Better use the wrapper that outomatically conform
--   to the things described below
--
--   Tables: Sorting
--   - Call TableGetSortSpecs() to retrieve latest sort specs for the table.
--     NULL when not sorting.
--   - When 'SpecsDirty == true' you should sort your data. It will be true when
--     sorting specs have changed since last call, or the first time. Make sure
--     to set 'SpecsDirty = false' after sorting, else you may wastefully sort
--     your data every frame!
--   - Lifetime: don't hold on this pointer over multiple frames or past any
--     subsequent call to BeginTable().
tableGetSortSpecs :: MonadIO m => m (Maybe (Ptr ImGuiTableSortSpecs))
tableGetSortSpecs :: forall (m :: * -> *).
MonadIO m =>
m (Maybe (Ptr ImGuiTableSortSpecs))
tableGetSortSpecs = IO (Maybe (Ptr ImGuiTableSortSpecs))
-> m (Maybe (Ptr ImGuiTableSortSpecs))
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  Ptr ImGuiTableSortSpecs
ptr <- [C.exp| ImGuiTableSortSpecs* { TableGetSortSpecs() } |]
  if Ptr ImGuiTableSortSpecs
ptr Ptr ImGuiTableSortSpecs -> Ptr ImGuiTableSortSpecs -> Bool
forall a. Eq a => a -> a -> Bool
== Ptr ImGuiTableSortSpecs
forall {b}. Ptr b
nullPtr then
    Maybe (Ptr ImGuiTableSortSpecs)
-> IO (Maybe (Ptr ImGuiTableSortSpecs))
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe (Ptr ImGuiTableSortSpecs)
forall a. Maybe a
Nothing
  else
    Maybe (Ptr ImGuiTableSortSpecs)
-> IO (Maybe (Ptr ImGuiTableSortSpecs))
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe (Ptr ImGuiTableSortSpecs)
 -> IO (Maybe (Ptr ImGuiTableSortSpecs)))
-> Maybe (Ptr ImGuiTableSortSpecs)
-> IO (Maybe (Ptr ImGuiTableSortSpecs))
forall a b. (a -> b) -> a -> b
$ Ptr ImGuiTableSortSpecs -> Maybe (Ptr ImGuiTableSortSpecs)
forall a. a -> Maybe a
Just Ptr ImGuiTableSortSpecs
ptr

tableClearSortSpecsDirty :: MonadIO m => Ptr ImGuiTableSortSpecs -> m ()
tableClearSortSpecsDirty :: forall (m :: * -> *). MonadIO m => Ptr ImGuiTableSortSpecs -> m ()
tableClearSortSpecsDirty Ptr ImGuiTableSortSpecs
specsPtr = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.block| void {
    $(ImGuiTableSortSpecs* specsPtr)->SpecsDirty = false;
  } |]

-- | Wraps @ImGui::TableGetColumnCount()@.
tableGetColumnCount :: MonadIO m => m CInt
tableGetColumnCount :: forall (m :: * -> *). MonadIO m => m CInt
tableGetColumnCount = IO CInt -> m CInt
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| int { TableGetColumnCount() } |]

-- | Wraps @ImGui::TableGetColumnIndex()@.
tableGetColumnIndex :: MonadIO m => m CInt
tableGetColumnIndex :: forall (m :: * -> *). MonadIO m => m CInt
tableGetColumnIndex = IO CInt -> m CInt
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| int { TableGetColumnIndex() } |]

-- | Wraps @ImGui::TableGetRowIndex()@.
tableGetRowIndex :: MonadIO m => m CInt
tableGetRowIndex :: forall (m :: * -> *). MonadIO m => m CInt
tableGetRowIndex = IO CInt -> m CInt
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| int { TableGetRowIndex() } |]

-- | Wraps @ImGui::TableGetColumnName
--   'Nothing' returns the current column name
tableGetColumnName :: MonadIO m => Maybe CInt -> m CString
tableGetColumnName :: forall (m :: * -> *). MonadIO m => Maybe CInt -> m CString
tableGetColumnName Maybe CInt
Nothing = Maybe CInt -> m CString
forall (m :: * -> *). MonadIO m => Maybe CInt -> m CString
tableGetColumnName (CInt -> Maybe CInt
forall a. a -> Maybe a
Just (-CInt
1))
tableGetColumnName (Just CInt
column_n) = IO CString -> m CString
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| const char* { TableGetColumnName($(int column_n)) } |]

-- | Wraps @ImGui::TableGetRowIndex()@.
--   'Nothing' returns the current column flags
tableGetColumnFlags :: MonadIO m => Maybe CInt -> m ImGuiTableColumnFlags
tableGetColumnFlags :: forall (m :: * -> *).
MonadIO m =>
Maybe CInt -> m ImGuiTableColumnFlags
tableGetColumnFlags Maybe CInt
Nothing = Maybe CInt -> m ImGuiTableColumnFlags
forall (m :: * -> *).
MonadIO m =>
Maybe CInt -> m ImGuiTableColumnFlags
tableGetColumnFlags (CInt -> Maybe CInt
forall a. a -> Maybe a
Just (-CInt
1))
tableGetColumnFlags (Just CInt
column_n) = IO ImGuiTableColumnFlags -> m ImGuiTableColumnFlags
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| ImGuiTableColumnFlags { TableGetColumnFlags($(int column_n)) } |]

-- | Wraps @ImGui::TableSetColumnEnabled()@.
tableSetColumnEnabled :: MonadIO m => CInt -> CBool -> m ()
tableSetColumnEnabled :: forall (m :: * -> *). MonadIO m => CInt -> CBool -> m ()
tableSetColumnEnabled CInt
column_n CBool
v = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { TableSetColumnEnabled($(int column_n), $(bool v)) } |]

-- | Wraps @ImGui::TableSetBgColor()@.
--   'Nothing' sets the current row/column color
tableSetBgColor :: MonadIO m => ImGuiTableBgTarget -> ImU32 -> Maybe CInt -> m ()
tableSetBgColor :: forall (m :: * -> *).
MonadIO m =>
ImGuiTableBgTarget -> ImGuiID -> Maybe CInt -> m ()
tableSetBgColor ImGuiTableBgTarget
target ImGuiID
color Maybe CInt
Nothing = ImGuiTableBgTarget -> ImGuiID -> Maybe CInt -> m ()
forall (m :: * -> *).
MonadIO m =>
ImGuiTableBgTarget -> ImGuiID -> Maybe CInt -> m ()
tableSetBgColor ImGuiTableBgTarget
target ImGuiID
color (CInt -> Maybe CInt
forall a. a -> Maybe a
Just (-CInt
1))
tableSetBgColor ImGuiTableBgTarget
target ImGuiID
color (Just CInt
column_n) = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { TableSetBgColor($(ImGuiTableBgTarget target), $(ImU32 color), $(int column_n)) } |]

-- | Wraps @ImGui::TreeNode()@.
treeNode :: (MonadIO m) => CString -> m Bool
treeNode :: forall (m :: * -> *). MonadIO m => CString -> m Bool
treeNode CString
labelPtr = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (CBool
0 CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/=) (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| bool { TreeNode($(char* labelPtr)) } |]


-- | Wraps @ImGui::TreePush()@.
treePush :: (MonadIO m) => CString -> m ()
treePush :: forall (m :: * -> *). MonadIO m => CString -> m ()
treePush CString
labelPtr = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { TreePush($(char* labelPtr)) } |]


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


-- -- | Wraps @ImGui::Selectable()@.
-- selectable :: (MonadIO m) => CString -> m Bool
-- selectable labelPtr = liftIO do
--   (0 /=) <$> [C.exp| bool { Selectable($(char* labelPtr)) } |]


-- | Wraps @ImGui::Selectable()@.
selectable :: (MonadIO m) => CString -> CBool -> ImGuiSelectableFlags -> Ptr ImVec2 -> m Bool
selectable :: forall (m :: * -> *).
MonadIO m =>
CString -> CBool -> ImGuiSelectableFlags -> Ptr ImVec2 -> m Bool
selectable CString
labelPtr CBool
selected ImGuiSelectableFlags
flags Ptr ImVec2
size = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (CBool
0 CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/=) (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| bool { Selectable($(char* labelPtr), $(bool selected), $(ImGuiSelectableFlags flags), *$(ImVec2 *size)) } |]



-- | Wraps @ImGui::ListBox()@.
listBox :: (MonadIO m) => CString -> Ptr CInt -> Ptr CString -> CInt -> m Bool
listBox :: forall (m :: * -> *).
MonadIO m =>
CString -> Ptr CInt -> Ptr CString -> CInt -> m Bool
listBox CString
labelPtr Ptr CInt
iPtr Ptr CString
itemsPtr CInt
itemsLen = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (CBool
0 CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/=) (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| bool { ListBox($(char* labelPtr), $(int* iPtr), $(char** itemsPtr), $(int itemsLen)) }|]


-- | Wraps @ImGui::PlotHistogram()@.
plotHistogram :: (MonadIO m) => CString -> Ptr CFloat -> CInt -> m ()
plotHistogram :: forall (m :: * -> *).
MonadIO m =>
CString -> Ptr CFloat -> CInt -> m ()
plotHistogram CString
labelPtr Ptr CFloat
valuesPtr CInt
valuesLen = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { PlotHistogram($(char* labelPtr), $(float* valuesPtr), $(int valuesLen)) } |]


-- | Append to menu-bar of current window (requires 'ImGuiWindowFlagsMenuBar'
-- flag set on parent window).
--
-- Wraps @ImGui::BeginMenuBar()@.
beginMenuBar :: (MonadIO m) => m Bool
beginMenuBar :: forall (m :: * -> *). MonadIO m => m Bool
beginMenuBar = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (CBool
0 CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/=) (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| bool { BeginMenuBar() } |]


-- | Only call 'endMenuBar' if 'beginMenuBar' returns true!
--
-- Wraps @ImGui::EndMenuBar()@.
endMenuBar :: (MonadIO m) => m ()
endMenuBar :: forall (m :: * -> *). MonadIO m => m ()
endMenuBar = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { EndMenuBar(); } |]


-- | Create and append to a full screen menu-bar.
--
-- Wraps @ImGui::BeginMainMenuBar()@.
beginMainMenuBar :: (MonadIO m) => m Bool
beginMainMenuBar :: forall (m :: * -> *). MonadIO m => m Bool
beginMainMenuBar = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (CBool
0 CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/=) (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| bool { BeginMainMenuBar() } |]


-- | Only call 'endMainMenuBar' if 'beginMainMenuBar' returns true!
--
-- Wraps @ImGui::EndMainMenuBar()@.
endMainMenuBar :: (MonadIO m) => m ()
endMainMenuBar :: forall (m :: * -> *). MonadIO m => m ()
endMainMenuBar = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { EndMainMenuBar(); } |]


-- | Create a sub-menu entry.
--
-- Wraps @ImGui::BeginMenu()@.
beginMenu :: (MonadIO m) => CString -> m Bool
beginMenu :: forall (m :: * -> *). MonadIO m => CString -> m Bool
beginMenu CString
labelPtr = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (CBool
0 CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/=) (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| bool { BeginMenu($(char* labelPtr)) } |]


-- | Only call 'endMenu' if 'beginMenu' returns true!
--
-- Wraps @ImGui::EndMenu()@.
endMenu :: (MonadIO m) => m ()
endMenu :: forall (m :: * -> *). MonadIO m => m ()
endMenu = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
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) => CString -> m Bool
menuItem :: forall (m :: * -> *). MonadIO m => CString -> m Bool
menuItem CString
labelPtr = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (CBool
0 CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/=) (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| bool { MenuItem($(char* labelPtr)) } |]


-- | Create a @TabBar@ and start appending to it.
--
-- Wraps @ImGui::BeginTabBar@.
beginTabBar :: (MonadIO m) => CString -> ImGuiTabBarFlags -> m Bool
beginTabBar :: forall (m :: * -> *).
MonadIO m =>
CString -> ImGuiTabBarFlags -> m Bool
beginTabBar CString
tabBarID ImGuiTabBarFlags
flags = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (CBool
0 CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/=) (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| bool { BeginTabBar($(char* tabBarID), $(ImGuiTabBarFlags flags) ) } |]


-- | Finish appending elements to a tab bar. Only call if 'beginTabBar' returns @True@.
--
-- Wraps @ImGui::EndTabBar@.
endTabBar :: (MonadIO m) => m ()
endTabBar :: forall (m :: * -> *). MonadIO m => m ()
endTabBar = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { EndTabBar(); } |]


-- | Create a new tab. Returns @True@ if the tab is selected.
--
-- Wraps @ImGui::BeginTabItem@.
beginTabItem :: (MonadIO m) => CString -> Ptr CBool -> ImGuiTabBarFlags -> m Bool
beginTabItem :: forall (m :: * -> *).
MonadIO m =>
CString -> Ptr CBool -> ImGuiTabBarFlags -> m Bool
beginTabItem CString
namePtr Ptr CBool
refPtr ImGuiTabBarFlags
flags = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (CBool
0 CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/=) (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| bool { BeginTabItem($(char* namePtr), $(bool* refPtr), $(ImGuiTabBarFlags flags) ) } |]


-- | Finish appending elements to a tab. Only call if 'beginTabItem' returns @True@.
--
-- Wraps @ImGui::EndTabItem@.
endTabItem :: (MonadIO m) => m ()
endTabItem :: forall (m :: * -> *). MonadIO m => m ()
endTabItem = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { EndTabItem(); } |]


-- | Create a tab that behaves like a button. Returns @True@ when clicked. Cannot be selected in the tab bar.
--
-- Wraps @ImGui.TabItemButton@.
tabItemButton :: (MonadIO m) => CString -> ImGuiTabItemFlags -> m Bool
tabItemButton :: forall (m :: * -> *).
MonadIO m =>
CString -> ImGuiTabItemFlags -> m Bool
tabItemButton CString
namePtr ImGuiTabItemFlags
flags = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (CBool
0 CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/=) (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| bool { TabItemButton($(char* namePtr), $(ImGuiTabItemFlags flags) ) } |]


-- | Notify the tab bar (or the docking system) that a tab/window is about to close.
-- Useful to reduce visual flicker on reorderable tab bars.
--
-- __For tab-bar__: call after 'beginTabBar' and before tab submission. Otherwise, call with a window name.
setTabItemClosed :: (MonadIO m) => CString -> m ()
setTabItemClosed :: forall (m :: * -> *). MonadIO m => CString -> m ()
setTabItemClosed CString
namePtr = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { SetTabItemClosed($(char* namePtr)); } |]


-- | Begin/append a tooltip window to create full-featured tooltip (with any
-- kind of items).
--
-- Wraps @ImGui::BeginTooltip()@
beginTooltip :: (MonadIO m) => m ()
beginTooltip :: forall (m :: * -> *). MonadIO m => m ()
beginTooltip = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { BeginTooltip() } |]


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


-- | Returns 'True' if the popup is open, and you can start outputting to it.
--
-- Wraps @ImGui::BeginPopup()@
beginPopup :: (MonadIO m) => CString -> m Bool
beginPopup :: forall (m :: * -> *). MonadIO m => CString -> m Bool
beginPopup CString
popupIdPtr = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (CBool
0 CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/=) (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| bool { BeginPopup($(char* popupIdPtr)) } |]


-- | Returns 'True' if the modal is open, and you can start outputting to it.
--
-- Wraps @ImGui::BeginPopupModal()@
beginPopupModal :: (MonadIO m) => CString -> m Bool
beginPopupModal :: forall (m :: * -> *). MonadIO m => CString -> m Bool
beginPopupModal CString
popupIdPtr = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (CBool
0 CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/=) (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| bool { BeginPopupModal($(char* popupIdPtr)) } |]


-- | Only call 'endPopup' if 'beginPopup' or 'beginPopupModal' returns 'True'!
--
-- Wraps @ImGui::BeginPopupModal()@
endPopup :: (MonadIO m) => m ()
endPopup :: forall (m :: * -> *). MonadIO m => m ()
endPopup = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { EndPopup() } |]


-- | Call to mark popup as open (don't call every frame!).
--
-- Wraps @ImGui::OpenPopup()@
openPopup :: (MonadIO m) => CString -> m ()
openPopup :: forall (m :: * -> *). MonadIO m => CString -> m ()
openPopup CString
popupIdPtr = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { OpenPopup($(char* popupIdPtr)) } |]


-- | Open popup when clicked on last item.
--
-- Note: actually triggers on the mouse _released_ event to be consistent with popup behaviors.
--
-- Wraps @ImGui::OpenPopupOnItemClick()@
openPopupOnItemClick :: (MonadIO m) => CString -> ImGuiPopupFlags-> m ()
openPopupOnItemClick :: forall (m :: * -> *).
MonadIO m =>
CString -> ImGuiPopupFlags -> m ()
openPopupOnItemClick CString
popupIdPtr ImGuiPopupFlags
flags = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { OpenPopupOnItemClick($(char* popupIdPtr), $(ImGuiPopupFlags flags)) } |]


-- | Manually close the popup we have begin-ed into.
--
-- Wraps @ImGui::ClosePopup()@
closeCurrentPopup :: (MonadIO m) => m ()
closeCurrentPopup :: forall (m :: * -> *). MonadIO m => m ()
closeCurrentPopup = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { CloseCurrentPopup() } |]

-- | Open+begin popup when clicked on last item.
--
-- Use str_id==NULL to associate the popup to previous item.
--
-- If you want to use that on a non-interactive item such as 'text' you need to pass in an explicit ID here.
beginPopupContextItem :: (MonadIO m) => CString -> ImGuiPopupFlags-> m Bool
beginPopupContextItem :: forall (m :: * -> *).
MonadIO m =>
CString -> ImGuiPopupFlags -> m Bool
beginPopupContextItem CString
popupIdPtr ImGuiPopupFlags
flags = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (CBool
0 CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/=) (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| bool { BeginPopupContextItem($(char* popupIdPtr), $(ImGuiPopupFlags flags)) } |]

-- | Open+begin popup when clicked on current window.
beginPopupContextWindow :: (MonadIO m) => CString -> ImGuiPopupFlags-> m Bool
beginPopupContextWindow :: forall (m :: * -> *).
MonadIO m =>
CString -> ImGuiPopupFlags -> m Bool
beginPopupContextWindow CString
popupIdPtr ImGuiPopupFlags
flags = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (CBool
0 CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/=) (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| bool { BeginPopupContextWindow($(char* popupIdPtr), $(ImGuiPopupFlags flags)) } |]

-- | Open+begin popup when clicked in void (where there are no windows).
beginPopupContextVoid :: (MonadIO m) => CString -> ImGuiPopupFlags-> m Bool
beginPopupContextVoid :: forall (m :: * -> *).
MonadIO m =>
CString -> ImGuiPopupFlags -> m Bool
beginPopupContextVoid CString
popupIdPtr ImGuiPopupFlags
flags = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (CBool
0 CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/=) (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| bool { BeginPopupContextVoid($(char* popupIdPtr), $(ImGuiPopupFlags flags)) } |]

-- | Query popup status
--
-- - return 'True' if the popup is open at the current 'beginPopup' level of the popup stack.
-- - with 'ImGuiPopupFlags_AnyPopupId': return 'True' if any popup is open at the current 'beginPopup' level of the popup stack.
-- - with 'ImGuiPopupFlags_AnyPopupId' | 'ImGuiPopupFlags_AnyPopupLevel': return 'True' if any popup is open.
--
-- Wraps @ImGui::IsPopupOpen()@
isPopupOpen :: (MonadIO m) => CString -> ImGuiPopupFlags-> m Bool
isPopupOpen :: forall (m :: * -> *).
MonadIO m =>
CString -> ImGuiPopupFlags -> m Bool
isPopupOpen CString
popupIdPtr ImGuiPopupFlags
flags = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (CBool
0 CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/=) (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| bool { IsPopupOpen($(char* popupIdPtr), $(ImGuiPopupFlags flags)) } |]


-- | Is the last item hovered? (and usable, aka not blocked by a popup, etc.).
--
-- Wraps @ImGui::IsItemHovered()@
isItemHovered :: (MonadIO m) => m Bool
isItemHovered :: forall (m :: * -> *). MonadIO m => m Bool
isItemHovered = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (CBool
0 CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/=) (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| bool { IsItemHovered() } |]


-- | Get draw list associated to the current window.
getWindowDrawList :: (MonadIO m) => m DrawList
getWindowDrawList :: forall (m :: * -> *). MonadIO m => m DrawList
getWindowDrawList = IO DrawList -> m DrawList
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  Ptr ImDrawList -> DrawList
DrawList (Ptr ImDrawList -> DrawList) -> IO (Ptr ImDrawList) -> IO DrawList
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp|
    ImDrawList* {
      GetWindowDrawList()
    }
  |]

-- | Get current window position in screen space.
--
-- Useful if you want to do your own drawing via the "DrawList" API.
getWindowPos :: (MonadIO m) => m ImVec2
getWindowPos :: forall (m :: * -> *). MonadIO m => m ImVec2
getWindowPos = IO ImVec2 -> m ImVec2
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (Ptr ImVec2 -> IO ()) -> IO ImVec2
forall a. Storable a => (Ptr a -> IO ()) -> IO a
C.withPtr_ \Ptr ImVec2
ptr ->
    [C.block|
      void {
        *$(ImVec2 * ptr) = GetWindowPos();
      }
    |]

getWindowSize :: (MonadIO m) => m ImVec2
getWindowSize :: forall (m :: * -> *). MonadIO m => m ImVec2
getWindowSize = IO ImVec2 -> m ImVec2
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (Ptr ImVec2 -> IO ()) -> IO ImVec2
forall a. Storable a => (Ptr a -> IO ()) -> IO a
C.withPtr_ \Ptr ImVec2
ptr ->
    [C.block|
      void {
        *$(ImVec2 * ptr) = GetWindowSize();
      }
    |]

getWindowWidth :: (MonadIO m) => m CFloat
getWindowWidth :: forall (m :: * -> *). MonadIO m => m CFloat
getWindowWidth = IO CFloat -> m CFloat
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| float { GetWindowWidth() } |]

getWindowHeight :: (MonadIO m) => m CFloat
getWindowHeight :: forall (m :: * -> *). MonadIO m => m CFloat
getWindowHeight = IO CFloat -> m CFloat
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| float { GetWindowHeight() } |]

-- | Set next window position. Call before `begin` Use pivot=(0.5,0.5) to center on given point, etc.
--
-- Wraps @ImGui::SetNextWindowPos()@
setNextWindowPos :: (MonadIO m) => Ptr ImVec2 -> ImGuiCond -> Maybe (Ptr ImVec2) -> m ()
setNextWindowPos :: forall (m :: * -> *).
MonadIO m =>
Ptr ImVec2 -> ImGuiCond -> Maybe (Ptr ImVec2) -> m ()
setNextWindowPos Ptr ImVec2
posPtr ImGuiCond
cond (Just Ptr ImVec2
pivotPtr) = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { SetNextWindowPos(*$(ImVec2* posPtr), $(ImGuiCond cond), *$(ImVec2* pivotPtr)) } |]
setNextWindowPos Ptr ImVec2
posPtr ImGuiCond
cond Maybe (Ptr ImVec2)
Nothing = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { SetNextWindowPos(*$(ImVec2* posPtr), $(ImGuiCond cond)) } |]


-- | Set next window size. Call before `begin`
--
-- Wraps @ImGui::SetNextWindowSize()@
setNextWindowSize :: (MonadIO m) => Ptr ImVec2 -> ImGuiCond -> m ()
setNextWindowSize :: forall (m :: * -> *). MonadIO m => Ptr ImVec2 -> ImGuiCond -> m ()
setNextWindowSize Ptr ImVec2
sizePtr ImGuiCond
cond = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { SetNextWindowSize(*$(ImVec2* sizePtr), $(ImGuiCond cond)) } |]


-- | Set next window size and position to match current display size.
--
-- Call before `begin`.
--
-- Wraps @ImGui::SetNextWindowPos()@, @ImGui::SetNextWindowSize()@
setNextWindowFullscreen :: (MonadIO m) => m ()
setNextWindowFullscreen :: forall (m :: * -> *). MonadIO m => m ()
setNextWindowFullscreen = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO
  [C.block|
    void {
      SetNextWindowPos(ImVec2(0, 0));
      SetNextWindowSize(GetIO().DisplaySize);
    }
  |]

-- | Set next window content size (~ scrollable client area, which enforce the range of scrollbars). Not including window decorations (title bar, menu bar, etc.) nor WindowPadding. call before `begin`
--
-- Wraps @ImGui::SetNextWindowContentSize()@
setNextWindowContentSize :: (MonadIO m) => Ptr ImVec2 -> m ()
setNextWindowContentSize :: forall (m :: * -> *). MonadIO m => Ptr ImVec2 -> m ()
setNextWindowContentSize Ptr ImVec2
sizePtr = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { SetNextWindowContentSize(*$(ImVec2* sizePtr)) } |]


-- | Set next window size limits. use -1,-1 on either X/Y axis to preserve the current size. Sizes will be rounded down.
--
-- Wraps @ImGui::SetNextWindowContentSize()@
setNextWindowSizeConstraints :: (MonadIO m) => Ptr ImVec2 -> Ptr ImVec2 -> m ()
setNextWindowSizeConstraints :: forall (m :: * -> *). MonadIO m => Ptr ImVec2 -> Ptr ImVec2 -> m ()
setNextWindowSizeConstraints Ptr ImVec2
sizeMinPtr Ptr ImVec2
sizeMaxPtr = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { SetNextWindowSizeConstraints(*$(ImVec2* sizeMinPtr), *$(ImVec2* sizeMaxPtr)) } |]


-- | Set next window collapsed state. call before `begin`
--
-- Wraps @ImGui::SetNextWindowCollapsed()@
setNextWindowCollapsed :: (MonadIO m) => CBool -> ImGuiCond -> m ()
setNextWindowCollapsed :: forall (m :: * -> *). MonadIO m => CBool -> ImGuiCond -> m ()
setNextWindowCollapsed CBool
b ImGuiCond
cond = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { SetNextWindowCollapsed($(bool b), $(ImGuiCond cond)) } |]


-- | Set next window background color alpha. helper to easily override the Alpha component of `ImGuiCol_WindowBg`, `ChildBg`, `PopupBg`. you may also use `ImGuiWindowFlags_NoBackground`.
--
-- Wraps @ImGui::SetNextWindowBgAlpha()@
setNextWindowBgAlpha :: (MonadIO m) => CFloat -> m ()
setNextWindowBgAlpha :: forall (m :: * -> *). MonadIO m => CFloat -> m ()
setNextWindowBgAlpha CFloat
alpha = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { SetNextWindowBgAlpha($(float alpha)) } |]


-- | undo a sameLine or force a new line when in an horizontal-layout context.
--
-- Wraps @ImGui::NewLine()@
newLine :: (MonadIO m) => m ()
newLine :: forall (m :: * -> *). MonadIO m => m ()
newLine = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { NewLine() } |]


-- | Add vertical spacing.
--
-- Wraps @ImGui::Spacing()@
spacing :: (MonadIO m) => m ()
spacing :: forall (m :: * -> *). MonadIO m => m ()
spacing = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { Spacing() } |]


-- | Add a dummy item of given size. unlike `invisibleButton`, `dummy` won't take the mouse click or be navigable into.
--
-- Wraps @ImGui::Dummy()@
dummy :: (MonadIO m) => Ptr ImVec2 -> m ()
dummy :: forall (m :: * -> *). MonadIO m => Ptr ImVec2 -> m ()
dummy Ptr ImVec2
sizePtr = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { Dummy(*$(ImVec2* sizePtr)) } |]


-- | Move content position toward the right, by indent_w, or style.IndentSpacing if indent_w <= 0
--
-- Wraps @ImGui::Indent()@
indent :: (MonadIO m) => CFloat -> m ()
indent :: forall (m :: * -> *). MonadIO m => CFloat -> m ()
indent CFloat
indent_w = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { Indent($(float indent_w)) } |]


-- | Move content position back to the left, by indent_w, or style.IndentSpacing if indent_w <= 0
--
-- Wraps @ImGui::Unindent()@
unindent :: (MonadIO m) => CFloat -> m ()
unindent :: forall (m :: * -> *). MonadIO m => CFloat -> m ()
unindent CFloat
indent_w = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { Unindent($(float indent_w)) } |]


-- | Affect large frame+labels widgets only.
--
-- Wraps @ImGui::SetNextItemWidth()@
setNextItemWidth :: (MonadIO m) => CFloat -> m ()
setNextItemWidth :: forall (m :: * -> *). MonadIO m => CFloat -> m ()
setNextItemWidth CFloat
itemWidth = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { SetNextItemWidth($(float itemWidth)) } |]


-- Wraps @ImGui::PushItemWidth()@
pushItemWidth :: (MonadIO m) => CFloat -> m ()
pushItemWidth :: forall (m :: * -> *). MonadIO m => CFloat -> m ()
pushItemWidth CFloat
itemWidth = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { PushItemWidth($(float itemWidth)) } |]


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


-- | lock horizontal starting position
--
--  Wraps @ImGui::BeginGroup()@
beginGroup :: (MonadIO m) => m ()
beginGroup :: forall (m :: * -> *). MonadIO m => m ()
beginGroup = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { BeginGroup() } |]


-- | unlock horizontal starting position + capture the whole group bounding box into one "item" (so you can use `isItemHovered` or layout primitives such as `sameLine` on whole group, etc.)
--
-- Wraps @ImGui::EndGroup()@
endGroup :: (MonadIO m) => m ()
endGroup :: forall (m :: * -> *). MonadIO m => m ()
endGroup = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { EndGroup() } |]


-- | Vertically align upcoming text baseline to FramePadding.y so that it will align properly to regularly framed items (call if you have text on a line before a framed item)
--
-- Wraps @ImGui::AlignTextToFramePadding()@
alignTextToFramePadding :: (MonadIO m) => m ()
alignTextToFramePadding :: forall (m :: * -> *). MonadIO m => m ()
alignTextToFramePadding = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { AlignTextToFramePadding() } |]


-- | Set cursor position in window-local coordinates
--
-- Wraps @ImGui::SetCursorPos()@
setCursorPos :: (MonadIO m) => Ptr ImVec2 -> m ()
setCursorPos :: forall (m :: * -> *). MonadIO m => Ptr ImVec2 -> m ()
setCursorPos Ptr ImVec2
posPtr = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { SetCursorPos(*$(ImVec2* posPtr)) } |]

-- | Cursor position in absolute coordinates.
--
-- Useful to work with 'DrawList' API.
--
-- Generally top-left == @GetMainViewport()->Pos == (0,0)@ in single viewport mode,
-- and bottom-right == @GetMainViewport()->Pos+Size == io.DisplaySize@ in single-viewport mode.
getCursorScreenPos :: (MonadIO m) => m ImVec2
getCursorScreenPos :: forall (m :: * -> *). MonadIO m => m ImVec2
getCursorScreenPos = IO ImVec2 -> m ImVec2
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (Ptr ImVec2 -> IO ()) -> IO ImVec2
forall a. Storable a => (Ptr a -> IO ()) -> IO a
C.withPtr_ \Ptr ImVec2
ptr ->
    [C.block|
      void {
        *$(ImVec2 * ptr) = GetCursorScreenPos();
      }
    |]


-- | Modify a style color by pushing to the shared stack. always use this if you modify the style after `newFrame`
--
-- Wraps @ImGui::PushStyleColor()@
pushStyleColor :: (MonadIO m) => ImGuiCol -> Ptr ImVec4 -> m ()
pushStyleColor :: forall (m :: * -> *). MonadIO m => ImGuiCol -> Ptr ImVec4 -> m ()
pushStyleColor ImGuiCol
col Ptr ImVec4
colorPtr = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { PushStyleColor($(ImGuiCol col), *$(ImVec4 *colorPtr)) } |]


-- | Remove style color modifications from the shared stack
--
-- Wraps @ImGui::PopStyleColor()@
popStyleColor :: (MonadIO m) => CInt -> m ()
popStyleColor :: forall (m :: * -> *). MonadIO m => CInt -> m ()
popStyleColor CInt
n = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { PopStyleColor($(int n)) } |]


-- | Modify a style variable by pushing to the shared stack. always use this if you modify the style after `newFrame`
--
-- Wraps @ImGui::PushStyleVar()@
pushStyleVar :: (MonadIO m) => ImGuiStyleVar -> Ptr ImVec2 -> m ()
pushStyleVar :: forall (m :: * -> *).
MonadIO m =>
ImGuiStyleVar -> Ptr ImVec2 -> m ()
pushStyleVar ImGuiStyleVar
style Ptr ImVec2
valPtr = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { PushStyleVar($(ImGuiStyleVar style), *$(ImVec2* valPtr)) } |]


-- | Remove style variable modifications from the shared stack
--
-- Wraps @ImGui::PopStyleVar()@
popStyleVar :: (MonadIO m) => CInt -> m ()
popStyleVar :: forall (m :: * -> *). MonadIO m => CInt -> m ()
popStyleVar CInt
n = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { PopStyleVar($(int n)) } |]


-- | Push integer into the ID stack (will hash int).
--
-- Wraps @ImGui::PushId@
pushIDInt :: (MonadIO m) => CInt -> m ()
pushIDInt :: forall (m :: * -> *). MonadIO m => CInt -> m ()
pushIDInt CInt
intId = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { PushID($(int intId)) } |]

-- | Push pointer into the ID stack (will hash pointer).
--
-- Wraps @ImGui::PushId@
pushIDPtr :: (MonadIO m) => Ptr a -> m ()
pushIDPtr :: forall (m :: * -> *) a. MonadIO m => Ptr a -> m ()
pushIDPtr Ptr a
ptr = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { PushID($(void * ptr_)) } |]
  where
    ptr_ :: Ptr b
ptr_ = Ptr a -> Ptr b
forall a b. Ptr a -> Ptr b
castPtr Ptr a
ptr

-- | Push string into the ID stack (will hash string).
--
-- Wraps @ImGui::PushId@
pushIDStr :: (MonadIO m) => CString -> m ()
pushIDStr :: forall (m :: * -> *). MonadIO m => CString -> m ()
pushIDStr CString
strId = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { PushID($(char * strId)) } |]

-- | Push string into the ID stack (will hash string).
--
-- Wraps @ImGui::PushId@
pushIDStrLen :: (MonadIO m) => CStringLen -> m ()
pushIDStrLen :: forall (m :: * -> *). MonadIO m => CStringLen -> m ()
pushIDStrLen (CString
strBegin, Int
strLen) = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { PushID($(char * strBegin), $(char * strEnd)) } |]
  where
    strEnd :: Ptr b
strEnd = CString -> Int -> Ptr b
forall a b. Ptr a -> Int -> Ptr b
plusPtr CString
strBegin Int
strLen

popID :: (MonadIO m) => m ()
popID :: forall (m :: * -> *). MonadIO m => m ()
popID = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [C.exp| void { PopID() } |]


wantCaptureMouse :: MonadIO m => m Bool
wantCaptureMouse :: forall (m :: * -> *). MonadIO m => m Bool
wantCaptureMouse = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (CBool
0 CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/=) (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| bool { GetIO().WantCaptureMouse } |]

wantCaptureKeyboard :: MonadIO m => m Bool
wantCaptureKeyboard :: forall (m :: * -> *). MonadIO m => m Bool
wantCaptureKeyboard = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (CBool
0 CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/=) (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp| bool { GetIO().WantCaptureKeyboard } |]

-- | This draw list will be the first rendering one.
--
-- Useful to quickly draw shapes/text behind dear imgui contents.
getBackgroundDrawList :: (MonadIO m) => m DrawList
getBackgroundDrawList :: forall (m :: * -> *). MonadIO m => m DrawList
getBackgroundDrawList = IO DrawList -> m DrawList
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  Ptr ImDrawList -> DrawList
DrawList (Ptr ImDrawList -> DrawList) -> IO (Ptr ImDrawList) -> IO DrawList
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp|
    ImDrawList* {
      GetBackgroundDrawList()
    }
  |]

--  | This draw list will be the last rendered one.
--
-- Useful to quickly draw shapes/text over dear imgui contents.
getForegroundDrawList :: (MonadIO m) => m DrawList
getForegroundDrawList :: forall (m :: * -> *). MonadIO m => m DrawList
getForegroundDrawList = IO DrawList -> m DrawList
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  Ptr ImDrawList -> DrawList
DrawList (Ptr ImDrawList -> DrawList) -> IO (Ptr ImDrawList) -> IO DrawList
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [C.exp|
    ImDrawList* {
      GetForegroundDrawList()
    }
  |]

-- | Generate 32-bit encoded colors using DearImgui macros.
--
-- Follows @IMGUI_USE_BGRA_PACKED_COLOR@ define to put bytes in appropriate positions.
imCol32 :: CUChar -> CUChar -> CUChar -> CUChar -> ImU32
imCol32 :: CUChar -> CUChar -> CUChar -> CUChar -> ImGuiID
imCol32 CUChar
r CUChar
g CUChar
b CUChar
a = IO ImGuiID -> ImGuiID
forall a. IO a -> a
unsafePerformIO
  [C.exp|
    ImU32 {
      IM_COL32(
        $(unsigned char r),
        $(unsigned char g),
        $(unsigned char b),
        $(unsigned char a)
      )
    }
  |]