{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}

{-|
Module: DearImGui

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

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

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

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

    -- * Styles
  , Raw.styleColorsDark
  , Raw.styleColorsLight
  , Raw.styleColorsClassic

    -- * Windows
  , withWindow
  , withWindowOpen
  , withFullscreen
  , fullscreenFlags

  , begin
  , Raw.end

    -- ** Utilities

  , Raw.getWindowDrawList
  , Raw.getWindowPos
  , Raw.getWindowSize
  , Raw.getWindowWidth
  , Raw.getWindowHeight

    -- ** Manipulation
  , setNextWindowPos
  , setNextWindowSize
  , Raw.setNextWindowFullscreen
  , setNextWindowContentSize
  , setNextWindowSizeConstraints
  , setNextWindowCollapsed
  , setNextWindowBgAlpha

    -- ** Child Windows
  , withChild
  , withChildOpen
  , withChildContext
  , beginChild
  , Raw.endChild

    -- * Parameter stacks
  , withStyleColor
  , pushStyleColor
  , Raw.popStyleColor

  , withStyleVar
  , pushStyleVar
  , popStyleVar

  , withFont
  , Raw.Font.pushFont
  , Raw.Font.popFont
  , Raw.Font.Font

    -- * Cursor/Layout
  , Raw.separator
  , Raw.sameLine
  , Raw.newLine
  , Raw.spacing
  , dummy

  , withIndent
  , indent
  , unindent

  , setNextItemWidth
  , withItemWidth
  , pushItemWidth
  , Raw.popItemWidth

  , withGroup
  , Raw.beginGroup
  , Raw.endGroup

  , setCursorPos
  , Raw.alignTextToFramePadding

    -- * ID stack
  , withID
  , ToID(..)

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

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

    -- ** Combo Box
  , withCombo
  , withComboOpen
  , beginCombo
  , Raw.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
  , withTable
  , withTableOpen
  , TableOptions(..)
  , defTableOptions
  , beginTable
  , Raw.endTable

    -- *** Setup
  , tableSetupColumn
  , tableSetupColumnWith
  , TableColumnOptions(..)
  , defTableColumnOptions

  , Raw.tableHeadersRow
  , Raw.tableHeader
  , tableSetupScrollFreeze

    -- *** Rows
  , tableNextRow
  , tableNextRowWith
  , TableRowOptions(..)
  , defTableRowOptions

    -- *** Columns
  , tableNextColumn
  , tableSetColumnIndex

    -- *** Sorting
  , withSortableTable
  , TableSortingSpecs(..)

    -- *** Queries
  , tableGetColumnCount
  , tableGetColumnIndex
  , tableGetRowIndex
  , tableGetColumnName
  , tableGetColumnFlags
  , tableSetColumnEnabled
  , tableSetBgColor

    -- ** Trees
  , treeNode
  , treePush
  , Raw.treePop

    -- ** Selectables
  , selectable
  , selectableWith
  , SelectableOptions(..)
  , defSelectableOptions

    -- ** List Boxes
  , listBox

    -- ** Data Plotting
  , plotHistogram

    -- ** Menus
  , withMenuBar
  , withMenuBarOpen
  , Raw.beginMenuBar
  , Raw.endMenuBar

  , withMainMenuBar
  , withMainMenuBarOpen
  , Raw.beginMainMenuBar
  , Raw.endMainMenuBar

  , withMenu
  , withMenuOpen
  , beginMenu
  , Raw.endMenu

  , menuItem

    -- ** Tabs, tab bar
  , withTabBar
  , withTabBarOpen
  , beginTabBar
  , Raw.endTabBar

  , withTabItem
  , withTabItemOpen
  , beginTabItem
  , Raw.endTabItem
  , tabItemButton
  , setTabItemClosed

    -- ** Tooltips
  , withTooltip
  , Raw.beginTooltip
  , Raw.endTooltip

    -- * Popups/Modals

    -- ** Generic
  , withPopup
  , withPopupOpen
  , beginPopup
  , Raw.endPopup

    -- ** Modal
  , withPopupModal
  , withPopupModalOpen
  , beginPopupModal

    -- ** Item context
  , itemContextPopup
  , withPopupContextItemOpen
  , withPopupContextItem
  , beginPopupContextItem

    -- ** Window context
  , windowContextPopup
  , withPopupContextWindowOpen
  , withPopupContextWindow
  , beginPopupContextWindow

    -- ** Void context
  , voidContextPopup
  , withPopupContextVoidOpen
  , withPopupContextVoid
  , beginPopupContextVoid

    -- ** Manual
  , openPopup
  , openPopupOnItemClick
  , Raw.closeCurrentPopup

    -- ** Queries
  , isCurrentPopupOpen
  , isAnyPopupOpen
  , isAnyLevelPopupOpen

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

    -- * Utilities

    -- ** ListClipper
  , withListClipper
  , ClipItems(..)
  , ClipRange(..)

    -- ** Miscellaneous
  , Raw.getBackgroundDrawList
  , Raw.getForegroundDrawList
  , Raw.imCol32

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

-- base
import Control.Monad
  ( when )
import Data.Bool
import Data.Foldable
  ( foldl' )
import Foreign
import Foreign.C

-- dear-imgui
import DearImGui.Enums
import DearImGui.Internal.Text (Text)
import DearImGui.Structs
import qualified DearImGui.Internal.Text as Text
import qualified DearImGui.Raw as Raw
import qualified DearImGui.Raw.Font as Raw.Font
import qualified DearImGui.Raw.ListClipper as Raw.ListClipper

-- managed
import qualified Control.Monad.Managed as Managed

-- StateVar
import Data.StateVar
  ( HasGetter(get), HasSetter, ($=!) )

-- transformers
import Control.Monad.IO.Class
  ( MonadIO, liftIO )

-- unliftio
import UnliftIO (MonadUnliftIO)
import UnliftIO.Exception (bracket, bracket_)

-- vector
import qualified Data.Vector as V
import qualified Data.Vector.Storable as VS
import qualified Data.Vector.Unboxed as VU

-- | 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 Text
getVersion :: forall (m :: * -> *). MonadIO m => m Text
getVersion = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  IO CString
forall (m :: * -> *). MonadIO m => m CString
Raw.getVersion IO CString -> (CString -> IO Text) -> IO Text
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= CString -> IO Text
Text.peekCString

-- | 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()@ with default options.
begin :: MonadIO m => Text -> m Bool
begin :: forall (m :: * -> *). MonadIO m => Text -> m Bool
begin Text
name = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
name \CString
namePtr ->
    CString -> Maybe (Ptr CBool) -> Maybe ImGuiWindowFlags -> IO Bool
forall (m :: * -> *).
MonadIO m =>
CString -> Maybe (Ptr CBool) -> Maybe ImGuiWindowFlags -> m Bool
Raw.begin CString
namePtr Maybe (Ptr CBool)
forall a. Maybe a
Nothing Maybe ImGuiWindowFlags
forall a. Maybe a
Nothing

-- | Append items to a window.
--
-- Action will get 'False' if the window is collapsed or fully clipped.
--
-- You may append multiple times to the same window during the same frame
-- by calling 'withWindow' in multiple places.
withWindow :: MonadUnliftIO m => Text -> (Bool -> m a) -> m a
withWindow :: forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (Bool -> m a) -> m a
withWindow Text
name = m Bool -> (Bool -> m ()) -> (Bool -> m a) -> m a
forall (m :: * -> *) a b c.
MonadUnliftIO m =>
m a -> (a -> m b) -> (a -> m c) -> m c
bracket (Text -> m Bool
forall (m :: * -> *). MonadIO m => Text -> m Bool
begin Text
name) (m () -> Bool -> m ()
forall a b. a -> b -> a
const m ()
forall (m :: * -> *). MonadIO m => m ()
Raw.end)

-- | Append items to a window unless it is collapsed or fully clipped.
--
-- You may append multiple times to the same window during the same frame
-- by calling 'withWindowOpen' in multiple places.
withWindowOpen :: MonadUnliftIO m => Text -> m () -> m ()
withWindowOpen :: forall (m :: * -> *). MonadUnliftIO m => Text -> m () -> m ()
withWindowOpen Text
name m ()
action =
  Text -> (Bool -> m ()) -> m ()
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (Bool -> m a) -> m a
withWindow Text
name (Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
`when` m ()
action)

-- | Append items to a fullscreen window.
--
-- The action runs inside a window that is set to behave as a backdrop.
-- It has no typical window decorations, ignores events and does not jump to front.
--
-- You may append multiple times to it during the same frame
-- by calling 'withFullscreen' in multiple places.
withFullscreen :: MonadUnliftIO m => m () -> m ()
withFullscreen :: forall (m :: * -> *). MonadUnliftIO m => m () -> m ()
withFullscreen m ()
action = m Bool -> (Bool -> m ()) -> (Bool -> m ()) -> m ()
forall (m :: * -> *) a b c.
MonadUnliftIO m =>
m a -> (a -> m b) -> (a -> m c) -> m c
bracket m Bool
open Bool -> m ()
forall {a}. a -> m ()
close (Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
`when` m ()
action)
  where
    open :: m Bool
open = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
      IO ()
forall (m :: * -> *). MonadIO m => m ()
Raw.setNextWindowFullscreen
      Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
"FullScreen" \CString
namePtr ->
        CString -> Maybe (Ptr CBool) -> Maybe ImGuiWindowFlags -> IO Bool
forall (m :: * -> *).
MonadIO m =>
CString -> Maybe (Ptr CBool) -> Maybe ImGuiWindowFlags -> m Bool
Raw.begin CString
namePtr (Ptr CBool -> Maybe (Ptr CBool)
forall a. a -> Maybe a
Just Ptr CBool
forall a. Ptr a
nullPtr) (ImGuiWindowFlags -> Maybe ImGuiWindowFlags
forall a. a -> Maybe a
Just ImGuiWindowFlags
fullscreenFlags)

    close :: a -> m ()
close = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> (a -> IO ()) -> a -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO () -> a -> IO ()
forall a b. a -> b -> a
const IO ()
forall (m :: * -> *). MonadIO m => m ()
Raw.end

fullscreenFlags :: ImGuiWindowFlags
fullscreenFlags :: ImGuiWindowFlags
fullscreenFlags = (ImGuiWindowFlags -> ImGuiWindowFlags -> ImGuiWindowFlags)
-> ImGuiWindowFlags -> [ImGuiWindowFlags] -> ImGuiWindowFlags
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' ImGuiWindowFlags -> ImGuiWindowFlags -> ImGuiWindowFlags
forall a. Bits a => a -> a -> a
(.|.) ImGuiWindowFlags
forall a. Bits a => a
zeroBits
  [ ImGuiWindowFlags
ImGuiWindowFlags_NoBackground
  , ImGuiWindowFlags
ImGuiWindowFlags_NoBringToFrontOnFocus
  , ImGuiWindowFlags
ImGuiWindowFlags_NoDecoration
  , ImGuiWindowFlags
ImGuiWindowFlags_NoFocusOnAppearing
  , ImGuiWindowFlags
ImGuiWindowFlags_NoMove
  , ImGuiWindowFlags
ImGuiWindowFlags_NoResize
  , ImGuiWindowFlags
ImGuiWindowFlags_NoSavedSettings
  , ImGuiWindowFlags
ImGuiWindowFlags_NoScrollbar
  , ImGuiWindowFlags
ImGuiWindowFlags_NoScrollWithMouse
  , ImGuiWindowFlags
ImGuiWindowFlags_NoTitleBar
  ]


-- | 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 => Text -> ImVec2 -> Bool -> ImGuiWindowFlags -> m Bool
beginChild :: forall (m :: * -> *).
MonadIO m =>
Text -> ImVec2 -> Bool -> ImGuiWindowFlags -> m Bool
beginChild Text
name ImVec2
size Bool
border ImGuiWindowFlags
flags = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
name \CString
namePtr ->
    ImVec2 -> (Ptr ImVec2 -> IO Bool) -> IO Bool
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with ImVec2
size \Ptr ImVec2
sizePtr ->
      CString -> Ptr ImVec2 -> CBool -> ImGuiWindowFlags -> IO Bool
forall (m :: * -> *).
MonadIO m =>
CString -> Ptr ImVec2 -> CBool -> ImGuiWindowFlags -> m Bool
Raw.beginChild CString
namePtr Ptr ImVec2
sizePtr (CBool -> CBool -> Bool -> CBool
forall a. a -> a -> Bool -> a
bool CBool
0 CBool
1 Bool
border) ImGuiWindowFlags
flags

-- | Action wrapper for child windows.
--
-- Action will get 'False' if the child region is collapsed or fully clipped.
withChild :: MonadUnliftIO m => Text -> ImVec2 -> Bool -> ImGuiWindowFlags -> (Bool -> m a) -> m a
withChild :: forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> ImVec2 -> Bool -> ImGuiWindowFlags -> (Bool -> m a) -> m a
withChild Text
name ImVec2
size Bool
border ImGuiWindowFlags
flags = m Bool -> (Bool -> m ()) -> (Bool -> m a) -> m a
forall (m :: * -> *) a b c.
MonadUnliftIO m =>
m a -> (a -> m b) -> (a -> m c) -> m c
bracket (Text -> ImVec2 -> Bool -> ImGuiWindowFlags -> m Bool
forall (m :: * -> *).
MonadIO m =>
Text -> ImVec2 -> Bool -> ImGuiWindowFlags -> m Bool
beginChild Text
name ImVec2
size Bool
border ImGuiWindowFlags
flags) (m () -> Bool -> m ()
forall a b. a -> b -> a
const m ()
forall (m :: * -> *). MonadIO m => m ()
Raw.endChild)

-- | Action-skipping wrapper for child windows.
--
-- Action will be skipped if the child region is collapsed or fully clipped.
withChildOpen :: MonadUnliftIO m => Text -> ImVec2 -> Bool -> ImGuiWindowFlags -> m () -> m ()
withChildOpen :: forall (m :: * -> *).
MonadUnliftIO m =>
Text -> ImVec2 -> Bool -> ImGuiWindowFlags -> m () -> m ()
withChildOpen Text
name ImVec2
size Bool
border ImGuiWindowFlags
flags m ()
action =
  Text
-> ImVec2 -> Bool -> ImGuiWindowFlags -> (Bool -> m ()) -> m ()
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> ImVec2 -> Bool -> ImGuiWindowFlags -> (Bool -> m a) -> m a
withChild Text
name ImVec2
size Bool
border ImGuiWindowFlags
flags (Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
`when` m ()
action)

-- | Action wrapper to run in a context of another child window addressed by its name.
--
-- Action will get 'False' if the child region is collapsed or fully clipped.
withChildContext :: MonadUnliftIO m => Text -> (Bool -> m a) -> m a
withChildContext :: forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (Bool -> m a) -> m a
withChildContext Text
name Bool -> m a
action =
  m Bool -> (Bool -> m ()) -> (Bool -> m a) -> m a
forall (m :: * -> *) a b c.
MonadUnliftIO m =>
m a -> (a -> m b) -> (a -> m c) -> m c
bracket
    (IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
name CString -> IO Bool
forall (m :: * -> *). MonadIO m => CString -> m Bool
Raw.beginChildContext)
    (m () -> Bool -> m ()
forall a b. a -> b -> a
const m ()
forall (m :: * -> *). MonadIO m => m ()
Raw.endChild)
    Bool -> m a
action


-- | Plain text.
text :: MonadIO m => Text -> m ()
text :: forall (m :: * -> *). MonadIO m => Text -> m ()
text Text
t = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  Text -> (CString -> IO ()) -> IO ()
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
t \CString
textPtr ->
    CString -> Maybe CString -> IO ()
forall (m :: * -> *). MonadIO m => CString -> Maybe CString -> m ()
Raw.textUnformatted CString
textPtr Maybe CString
forall a. Maybe a
Nothing

-- | Colored text.
textColored :: (HasGetter ref ImVec4, MonadIO m) => ref -> Text -> m ()
textColored :: forall ref (m :: * -> *).
(HasGetter ref ImVec4, MonadIO m) =>
ref -> Text -> m ()
textColored ref
ref Text
t = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  ImVec4
currentValue <- ref -> IO ImVec4
forall t a (m :: * -> *). (HasGetter t a, MonadIO m) => t -> m a
get ref
ref
  ImVec4 -> (Ptr ImVec4 -> IO ()) -> IO ()
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with ImVec4
currentValue \Ptr ImVec4
refPtr ->
    Text -> (CString -> IO ()) -> IO ()
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
t ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ImVec4 -> CString -> IO ()
forall (m :: * -> *). MonadIO m => Ptr ImVec4 -> CString -> m ()
Raw.textColored Ptr ImVec4
refPtr

-- | Plain text in a "disabled" color according to current style.
textDisabled :: MonadIO m => Text -> m ()
textDisabled :: forall (m :: * -> *). MonadIO m => Text -> m ()
textDisabled Text
t = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  Text -> (CString -> IO ()) -> IO ()
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
t CString -> IO ()
forall (m :: * -> *). MonadIO m => CString -> m ()
Raw.textDisabled

-- | Plain text with a word-wrap capability.
--
-- 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'.
textWrapped :: MonadIO m => Text -> m ()
textWrapped :: forall (m :: * -> *). MonadIO m => Text -> m ()
textWrapped Text
t = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  Text -> (CString -> IO ()) -> IO ()
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
t CString -> IO ()
forall (m :: * -> *). MonadIO m => CString -> m ()
Raw.textWrapped

-- | Label+text combo aligned to other label+value widgets.
labelText :: MonadIO m => Text -> Text -> m ()
labelText :: forall (m :: * -> *). MonadIO m => Text -> Text -> m ()
labelText Text
label Text
t = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  Text -> (CString -> IO ()) -> IO ()
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
label \CString
labelPtr ->
    Text -> (CString -> IO ()) -> IO ()
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
t \CString
textPtr ->
      CString -> CString -> IO ()
forall (m :: * -> *). MonadIO m => CString -> CString -> m ()
Raw.labelText CString
labelPtr CString
textPtr

-- | Text with a little bullet aligned to the typical tree node.
bulletText :: MonadIO m => Text -> m ()
bulletText :: forall (m :: * -> *). MonadIO m => Text -> m ()
bulletText Text
t = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  Text -> (CString -> IO ()) -> IO ()
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
t CString -> IO ()
forall (m :: * -> *). MonadIO m => CString -> m ()
Raw.bulletText

-- | A button. Returns 'True' when clicked.
--
-- Wraps @ImGui::Button()@.
button :: MonadIO m => Text -> m Bool
button :: forall (m :: * -> *). MonadIO m => Text -> m Bool
button Text
label = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
label CString -> IO Bool
forall (m :: * -> *). MonadIO m => CString -> m Bool
Raw.button


-- | Button with @FramePadding=(0,0)@ to easily embed within text.
--
-- Wraps @ImGui::SmallButton()@.
smallButton :: MonadIO m => Text -> m Bool
smallButton :: forall (m :: * -> *). MonadIO m => Text -> m Bool
smallButton Text
label = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
label CString -> IO Bool
forall (m :: * -> *). MonadIO m => CString -> m Bool
Raw.smallButton


-- | 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 => Text -> ImVec2 -> ImGuiButtonFlags -> m Bool
invisibleButton :: forall (m :: * -> *).
MonadIO m =>
Text -> ImVec2 -> ImGuiButtonFlags -> m Bool
invisibleButton Text
label ImVec2
size ImGuiButtonFlags
flags = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
label \CString
labelPtr ->
    ImVec2 -> (Ptr ImVec2 -> IO Bool) -> IO Bool
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with ImVec2
size \Ptr ImVec2
sizePtr ->
      CString -> Ptr ImVec2 -> ImGuiButtonFlags -> IO Bool
forall (m :: * -> *).
MonadIO m =>
CString -> Ptr ImVec2 -> ImGuiButtonFlags -> m Bool
Raw.invisibleButton CString
labelPtr Ptr ImVec2
sizePtr ImGuiButtonFlags
flags


-- | Square button with an arrow shape.
--
-- Wraps @ImGui::ArrowButton()@.
arrowButton :: MonadIO m => Text -> ImGuiDir -> m Bool
arrowButton :: forall (m :: * -> *). MonadIO m => Text -> ImGuiDir -> m Bool
arrowButton Text
strId ImGuiDir
dir = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
strId \CString
strIdPtr ->
    CString -> ImGuiDir -> IO Bool
forall (m :: * -> *). MonadIO m => CString -> ImGuiDir -> m Bool
Raw.arrowButton CString
strIdPtr ImGuiDir
dir


-- | Wraps @ImGui::Checkbox()@.
checkbox :: (HasSetter ref Bool, HasGetter ref Bool, MonadIO m) => Text -> ref -> m Bool
checkbox :: forall ref (m :: * -> *).
(HasSetter ref Bool, HasGetter ref Bool, MonadIO m) =>
Text -> ref -> m Bool
checkbox Text
label ref
ref = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  Bool
currentValue <- ref -> IO Bool
forall t a (m :: * -> *). (HasGetter t a, MonadIO m) => t -> m a
get ref
ref
  CBool -> (Ptr CBool -> IO Bool) -> IO Bool
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with (CBool -> CBool -> Bool -> CBool
forall a. a -> a -> Bool -> a
bool CBool
0 CBool
1 Bool
currentValue) \Ptr CBool
boolPtr -> do
    Bool
changed <- Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
label \CString
labelPtr ->
      CString -> Ptr CBool -> IO Bool
forall (m :: * -> *). MonadIO m => CString -> Ptr CBool -> m Bool
Raw.checkbox CString
labelPtr Ptr CBool
boolPtr

    Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
changed do
      CBool
newValue <- Ptr CBool -> IO CBool
forall a. Storable a => Ptr a -> IO a
peek Ptr CBool
boolPtr
      ref
ref ref -> Bool -> IO ()
forall t a (m :: * -> *).
(HasSetter t a, MonadIO m) =>
t -> a -> m ()
$=! (CBool
newValue CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
== CBool
1)

    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
changed


progressBar :: MonadIO m => Float -> Maybe Text -> m ()
progressBar :: forall (m :: * -> *). MonadIO m => Float -> Maybe Text -> m ()
progressBar Float
progress Maybe Text
overlay = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  Maybe Text -> (CString -> IO ()) -> IO ()
forall a. Maybe Text -> (CString -> IO a) -> IO a
Text.withCStringOrNull Maybe Text
overlay \CString
overlayPtr ->
    CFloat -> CString -> IO ()
forall (m :: * -> *). MonadIO m => CFloat -> CString -> m ()
Raw.progressBar (Float -> CFloat
CFloat Float
progress) CString
overlayPtr


-- | 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'.
--
-- Only call 'endCombo' if 'beginCombo' returns 'True'!
--
-- Wraps @ImGui::BeginCombo()@.
beginCombo :: MonadIO m => Text -> Text -> m Bool
beginCombo :: forall (m :: * -> *). MonadIO m => Text -> Text -> m Bool
beginCombo Text
label Text
previewValue = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$
  Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
label        \CString
labelPtr ->
  Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
previewValue \CString
previewValuePtr ->
  CString -> CString -> IO Bool
forall (m :: * -> *). MonadIO m => CString -> CString -> m Bool
Raw.beginCombo CString
labelPtr CString
previewValuePtr

-- | Create a combo box with a given label and preview value.
--
-- Action will get 'True' if the combo box is open.
-- In this state, you should populate the contents of the combo box - for example, by calling 'selectable'.
withCombo :: MonadUnliftIO m => Text -> Text -> (Bool -> m a) -> m a
withCombo :: forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> Text -> (Bool -> m a) -> m a
withCombo Text
label Text
previewValue =
  m Bool -> (Bool -> m ()) -> (Bool -> m a) -> m a
forall (m :: * -> *) a b c.
MonadUnliftIO m =>
m a -> (a -> m b) -> (a -> m c) -> m c
bracket (Text -> Text -> m Bool
forall (m :: * -> *). MonadIO m => Text -> Text -> m Bool
beginCombo Text
label Text
previewValue) (Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
`when` m ()
forall (m :: * -> *). MonadIO m => m ()
Raw.endCombo)

-- | Create a combo box with a given label and preview value.
--
-- Action will be called if the combo box is open to populate the contents
-- of the combo box - for example, by calling 'selectable'.
withComboOpen :: MonadUnliftIO m => Text -> Text -> m () -> m ()
withComboOpen :: forall (m :: * -> *).
MonadUnliftIO m =>
Text -> Text -> m () -> m ()
withComboOpen Text
label Text
previewValue m ()
action =
  Text -> Text -> (Bool -> m ()) -> m ()
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> Text -> (Bool -> m a) -> m a
withCombo Text
label Text
previewValue (Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
`when` m ()
action)

-- | Wraps @ImGui::Combo()@.
combo :: (MonadIO m, HasGetter ref Int, HasSetter ref Int) => Text -> ref -> [Text] -> m Bool
combo :: forall (m :: * -> *) ref.
(MonadIO m, HasGetter ref Int, HasSetter ref Int) =>
Text -> ref -> [Text] -> m Bool
combo Text
label ref
selectedIndex [Text]
items = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ Managed Bool -> (Bool -> IO Bool) -> IO Bool
forall a r. Managed a -> (a -> IO r) -> IO r
Managed.with Managed Bool
m Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return
  where
    m :: Managed Bool
m = do
      Int
i <- ref -> Managed Int
forall t a (m :: * -> *). (HasGetter t a, MonadIO m) => t -> m a
get ref
selectedIndex

      [CString]
cStrings <- (Text -> Managed CString) -> [Text] -> Managed [CString]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (\Text
str -> (forall r. (CString -> IO r) -> IO r) -> Managed CString
forall (m :: * -> *) a.
MonadManaged m =>
(forall r. (a -> IO r) -> IO r) -> m a
Managed.managed (Text -> (CString -> IO r) -> IO r
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
str)) [Text]
items
      CString
labelPtr <- (forall r. (CString -> IO r) -> IO r) -> Managed CString
forall (m :: * -> *) a.
MonadManaged m =>
(forall r. (a -> IO r) -> IO r) -> m a
Managed.managed ((forall r. (CString -> IO r) -> IO r) -> Managed CString)
-> (forall r. (CString -> IO r) -> IO r) -> Managed CString
forall a b. (a -> b) -> a -> b
$ Text -> (CString -> IO r) -> IO r
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
label
      Ptr CInt
iPtr     <- (forall r. (Ptr CInt -> IO r) -> IO r) -> Managed (Ptr CInt)
forall (m :: * -> *) a.
MonadManaged m =>
(forall r. (a -> IO r) -> IO r) -> m a
Managed.managed ((forall r. (Ptr CInt -> IO r) -> IO r) -> Managed (Ptr CInt))
-> (forall r. (Ptr CInt -> IO r) -> IO r) -> Managed (Ptr CInt)
forall a b. (a -> b) -> a -> b
$ CInt -> (Ptr CInt -> IO r) -> IO r
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
i)

      IO Bool -> Managed Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> Managed Bool) -> IO Bool -> Managed Bool
forall a b. (a -> b) -> a -> b
$ [CString] -> (Int -> Ptr CString -> IO Bool) -> IO Bool
forall a b. Storable a => [a] -> (Int -> Ptr a -> IO b) -> IO b
withArrayLen [CString]
cStrings \Int
len Ptr CString
itemsPtr -> do
        Bool
changed <- CString -> Ptr CInt -> Ptr CString -> CInt -> IO Bool
forall (m :: * -> *).
MonadIO m =>
CString -> Ptr CInt -> Ptr CString -> CInt -> m Bool
Raw.combo CString
labelPtr Ptr CInt
iPtr Ptr CString
itemsPtr (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
len)

        Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
changed do
          CInt
i' <- Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek Ptr CInt
iPtr
          ref
selectedIndex ref -> Int -> IO ()
forall t a (m :: * -> *).
(HasSetter t a, MonadIO m) =>
t -> a -> m ()
$=! CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
i'

        Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
changed


-- | Wraps @ImGui::DragFloat()@
dragFloat :: (MonadIO m, HasSetter ref Float, HasGetter ref Float) => Text -> ref -> Float -> Float -> Float -> m Bool
dragFloat :: forall (m :: * -> *) ref.
(MonadIO m, HasSetter ref Float, HasGetter ref Float) =>
Text -> ref -> Float -> Float -> Float -> m Bool
dragFloat Text
desc ref
ref Float
speed Float
minValue Float
maxValue = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  Float
currentValue <- ref -> IO Float
forall t a (m :: * -> *). (HasGetter t a, MonadIO m) => t -> m a
get ref
ref
  CFloat -> (Ptr CFloat -> IO Bool) -> IO Bool
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with (Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
currentValue) \Ptr CFloat
floatPtr -> do
    Bool
changed <- Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
desc \CString
descPtr ->
      CString -> Ptr CFloat -> CFloat -> CFloat -> CFloat -> IO Bool
forall (m :: * -> *).
MonadIO m =>
CString -> Ptr CFloat -> CFloat -> CFloat -> CFloat -> m Bool
Raw.dragFloat CString
descPtr Ptr CFloat
floatPtr (Float -> CFloat
CFloat Float
speed) (Float -> CFloat
CFloat Float
minValue) (Float -> CFloat
CFloat Float
maxValue)

    Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
changed do
      CFloat
newValue <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek Ptr CFloat
floatPtr
      ref
ref ref -> Float -> IO ()
forall t a (m :: * -> *).
(HasSetter t a, MonadIO m) =>
t -> a -> m ()
$=! CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
newValue

    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
changed


-- | Wraps @ImGui::DragFloat2()@
dragFloat2 :: (MonadIO m, HasSetter ref (Float, Float), HasGetter ref (Float, Float)) => Text -> ref -> Float -> Float -> Float -> m Bool
dragFloat2 :: forall (m :: * -> *) ref.
(MonadIO m, HasSetter ref (Float, Float),
 HasGetter ref (Float, Float)) =>
Text -> ref -> Float -> Float -> Float -> m Bool
dragFloat2 Text
desc ref
ref Float
speed Float
minValue Float
maxValue = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (Float
x, Float
y) <- ref -> IO (Float, Float)
forall t a (m :: * -> *). (HasGetter t a, MonadIO m) => t -> m a
get ref
ref
  [CFloat] -> (Ptr CFloat -> IO Bool) -> IO Bool
forall a b. Storable a => [a] -> (Ptr a -> IO b) -> IO b
withArray [ Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
x, Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
y ] \Ptr CFloat
floatPtr -> do
    Bool
changed <- Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
desc \CString
descPtr ->
      CString -> Ptr CFloat -> CFloat -> CFloat -> CFloat -> IO Bool
forall (m :: * -> *).
MonadIO m =>
CString -> Ptr CFloat -> CFloat -> CFloat -> CFloat -> m Bool
Raw.dragFloat2 CString
descPtr Ptr CFloat
floatPtr (Float -> CFloat
CFloat Float
speed) (Float -> CFloat
CFloat Float
minValue) (Float -> CFloat
CFloat Float
maxValue)

    Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
changed do
      [CFloat
x', CFloat
y'] <- Int -> Ptr CFloat -> IO [CFloat]
forall a. Storable a => Int -> Ptr a -> IO [a]
peekArray Int
2 Ptr CFloat
floatPtr
      ref
ref ref -> (Float, Float) -> IO ()
forall t a (m :: * -> *).
(HasSetter t a, MonadIO m) =>
t -> a -> m ()
$=! (CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
x', CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
y')

    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
changed

-- | Wraps @ImGui::DragFloat3()@
dragFloat3 :: (MonadIO m, HasSetter ref (Float, Float, Float), HasGetter ref (Float, Float, Float)) => Text -> ref -> Float -> Float -> Float -> m Bool
dragFloat3 :: forall (m :: * -> *) ref.
(MonadIO m, HasSetter ref (Float, Float, Float),
 HasGetter ref (Float, Float, Float)) =>
Text -> ref -> Float -> Float -> Float -> m Bool
dragFloat3 Text
desc ref
ref Float
speed Float
minValue Float
maxValue = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (Float
x, Float
y, Float
z) <- ref -> IO (Float, Float, Float)
forall t a (m :: * -> *). (HasGetter t a, MonadIO m) => t -> m a
get ref
ref
  [CFloat] -> (Ptr CFloat -> IO Bool) -> IO Bool
forall a b. Storable a => [a] -> (Ptr a -> IO b) -> IO b
withArray [ Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
x, Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
y, Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
z ] \Ptr CFloat
floatPtr -> do
    Bool
changed <- Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
desc \CString
descPtr ->
      CString -> Ptr CFloat -> CFloat -> CFloat -> CFloat -> IO Bool
forall (m :: * -> *).
MonadIO m =>
CString -> Ptr CFloat -> CFloat -> CFloat -> CFloat -> m Bool
Raw.dragFloat3 CString
descPtr Ptr CFloat
floatPtr (Float -> CFloat
CFloat Float
speed) (Float -> CFloat
CFloat Float
minValue) (Float -> CFloat
CFloat Float
maxValue)

    Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
changed do
      [CFloat
x', CFloat
y', CFloat
z'] <- Int -> Ptr CFloat -> IO [CFloat]
forall a. Storable a => Int -> Ptr a -> IO [a]
peekArray Int
3 Ptr CFloat
floatPtr
      ref
ref ref -> (Float, Float, Float) -> IO ()
forall t a (m :: * -> *).
(HasSetter t a, MonadIO m) =>
t -> a -> m ()
$=! (CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
x', CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
y', CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
z')

    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
changed


-- | Wraps @ImGui::DragFloat4()@
dragFloat4 :: (MonadIO m, HasSetter ref (Float, Float, Float, Float), HasGetter ref (Float, Float, Float, Float)) => Text -> ref -> Float -> Float -> Float -> m Bool
dragFloat4 :: forall (m :: * -> *) ref.
(MonadIO m, HasSetter ref (Float, Float, Float, Float),
 HasGetter ref (Float, Float, Float, Float)) =>
Text -> ref -> Float -> Float -> Float -> m Bool
dragFloat4 Text
desc ref
ref Float
speed Float
minValue Float
maxValue = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (Float
x, Float
y, Float
z, Float
u) <- ref -> IO (Float, Float, Float, Float)
forall t a (m :: * -> *). (HasGetter t a, MonadIO m) => t -> m a
get ref
ref
  [CFloat] -> (Ptr CFloat -> IO Bool) -> IO Bool
forall a b. Storable a => [a] -> (Ptr a -> IO b) -> IO b
withArray [ Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
x, Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
y, Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
z, Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
u ] \Ptr CFloat
floatPtr -> do
    Bool
changed <- Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
desc \CString
descPtr ->
      CString -> Ptr CFloat -> CFloat -> CFloat -> CFloat -> IO Bool
forall (m :: * -> *).
MonadIO m =>
CString -> Ptr CFloat -> CFloat -> CFloat -> CFloat -> m Bool
Raw.dragFloat4 CString
descPtr Ptr CFloat
floatPtr (Float -> CFloat
CFloat Float
speed) (Float -> CFloat
CFloat Float
minValue) (Float -> CFloat
CFloat Float
maxValue)

    Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
changed do
      [CFloat
x', CFloat
y', CFloat
z', CFloat
u'] <- Int -> Ptr CFloat -> IO [CFloat]
forall a. Storable a => Int -> Ptr a -> IO [a]
peekArray Int
4 Ptr CFloat
floatPtr
      ref
ref ref -> (Float, Float, Float, Float) -> IO ()
forall t a (m :: * -> *).
(HasSetter t a, MonadIO m) =>
t -> a -> m ()
$=! (CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
x', CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
y', CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
z', CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
u')

    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
changed

dragFloatRange2 :: (MonadIO m, HasSetter ref Float, HasGetter ref Float) => Text -> ref -> ref -> Float -> Float -> Float -> Text -> Text -> m Bool
dragFloatRange2 :: forall (m :: * -> *) ref.
(MonadIO m, HasSetter ref Float, HasGetter ref Float) =>
Text
-> ref -> ref -> Float -> Float -> Float -> Text -> Text -> m Bool
dragFloatRange2 Text
desc ref
refMin ref
refMax Float
speed Float
minValue Float
maxValue Text
minFmt Text
maxFmt = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  Float
curMin <- ref -> IO Float
forall t a (m :: * -> *). (HasGetter t a, MonadIO m) => t -> m a
get ref
refMin
  Float
curMax <- ref -> IO Float
forall t a (m :: * -> *). (HasGetter t a, MonadIO m) => t -> m a
get ref
refMax
  CFloat -> (Ptr CFloat -> IO Bool) -> IO Bool
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with (Float -> CFloat
CFloat Float
curMin) \Ptr CFloat
minPtr ->
    CFloat -> (Ptr CFloat -> IO Bool) -> IO Bool
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with (Float -> CFloat
CFloat Float
curMax) \Ptr CFloat
maxPtr -> do
      Bool
changed <-
        Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
desc \CString
descPtr ->
          Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
minFmt \CString
minFmtPtr ->
            Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
maxFmt \CString
maxFmtPtr ->
              CString
-> Ptr CFloat
-> Ptr CFloat
-> CFloat
-> CFloat
-> CFloat
-> CString
-> CString
-> ImGuiSliderFlags
-> IO Bool
forall (m :: * -> *).
MonadIO m =>
CString
-> Ptr CFloat
-> Ptr CFloat
-> CFloat
-> CFloat
-> CFloat
-> CString
-> CString
-> ImGuiSliderFlags
-> m Bool
Raw.dragFloatRange2
                CString
descPtr
                Ptr CFloat
minPtr Ptr CFloat
maxPtr
                (Float -> CFloat
CFloat Float
speed) (Float -> CFloat
CFloat Float
minValue) (Float -> CFloat
CFloat Float
maxValue)
                CString
minFmtPtr CString
maxFmtPtr
                ImGuiSliderFlags
ImGuiSliderFlags_AlwaysClamp

      Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
changed do
        CFloat Float
nextMin <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek Ptr CFloat
minPtr
        CFloat Float
nextMax <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek Ptr CFloat
maxPtr
        ref
refMin ref -> Float -> IO ()
forall t a (m :: * -> *).
(HasSetter t a, MonadIO m) =>
t -> a -> m ()
$=! Float
nextMin
        ref
refMax ref -> Float -> IO ()
forall t a (m :: * -> *).
(HasSetter t a, MonadIO m) =>
t -> a -> m ()
$=! Float
nextMax

      Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
changed

-- | Wraps @ImGui::DragFloat()@
dragInt :: (MonadIO m, HasSetter ref Int, HasGetter ref Int) => Text -> ref -> Float -> Int -> Int -> m Bool
dragInt :: forall (m :: * -> *) ref.
(MonadIO m, HasSetter ref Int, HasGetter ref Int) =>
Text -> ref -> Float -> Int -> Int -> m Bool
dragInt Text
label ref
ref Float
speed Int
minValue Int
maxValue = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  Int
currentValue <- ref -> IO Int
forall t a (m :: * -> *). (HasGetter t a, MonadIO m) => t -> m a
get ref
ref
  CInt -> (Ptr CInt -> IO Bool) -> IO Bool
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
currentValue) \Ptr CInt
vPtr -> do
    Bool
changed <-
      Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
label \CString
labelPtr ->
        Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
"%d" \CString
formatPtr ->
          CString
-> Ptr CInt
-> CFloat
-> CInt
-> CInt
-> CString
-> ImGuiSliderFlags
-> IO Bool
forall (m :: * -> *).
MonadIO m =>
CString
-> Ptr CInt
-> CFloat
-> CInt
-> CInt
-> CString
-> ImGuiSliderFlags
-> m Bool
Raw.dragInt
            CString
labelPtr
            Ptr CInt
vPtr
            (Float -> CFloat
CFloat Float
speed)
            (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
minValue)
            (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
maxValue)
            CString
formatPtr
            ImGuiSliderFlags
ImGuiSliderFlags_AlwaysClamp

    Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
changed do
      CInt
newValue <- Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek Ptr CInt
vPtr
      ref
ref ref -> Int -> IO ()
forall t a (m :: * -> *).
(HasSetter t a, MonadIO m) =>
t -> a -> m ()
$=! CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
newValue

    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
changed

-- | Wraps @ImGui::DragInt2()@
dragInt2 :: (MonadIO m, HasSetter ref (Int, Int), HasGetter ref (Int, Int)) => Text -> ref -> Float -> Int -> Int -> m Bool
dragInt2 :: forall (m :: * -> *) ref.
(MonadIO m, HasSetter ref (Int, Int), HasGetter ref (Int, Int)) =>
Text -> ref -> Float -> Int -> Int -> m Bool
dragInt2 Text
label ref
ref Float
speed Int
minValue Int
maxValue = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (Int
x, Int
y) <- ref -> IO (Int, Int)
forall t a (m :: * -> *). (HasGetter t a, MonadIO m) => t -> m a
get ref
ref
  [CInt] -> (Ptr CInt -> IO Bool) -> IO Bool
forall a b. Storable a => [a] -> (Ptr a -> IO b) -> IO b
withArray [ Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
x, Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
y ] \Ptr CInt
vPtr -> do
    Bool
changed <-
      Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
label \CString
labelPtr ->
        Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
"%d" \CString
formatPtr ->
          CString
-> Ptr CInt
-> CFloat
-> CInt
-> CInt
-> CString
-> ImGuiSliderFlags
-> IO Bool
forall (m :: * -> *).
MonadIO m =>
CString
-> Ptr CInt
-> CFloat
-> CInt
-> CInt
-> CString
-> ImGuiSliderFlags
-> m Bool
Raw.dragInt2
            CString
labelPtr
            Ptr CInt
vPtr
            (Float -> CFloat
CFloat Float
speed)
            (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
minValue)
            (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
maxValue)
            CString
formatPtr
            ImGuiSliderFlags
ImGuiSliderFlags_AlwaysClamp

    Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
changed do
      [CInt
x', CInt
y'] <- Int -> Ptr CInt -> IO [CInt]
forall a. Storable a => Int -> Ptr a -> IO [a]
peekArray Int
2 Ptr CInt
vPtr
      ref
ref ref -> (Int, Int) -> IO ()
forall t a (m :: * -> *).
(HasSetter t a, MonadIO m) =>
t -> a -> m ()
$=! (CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
x', CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
y')

    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
changed

-- | Wraps @ImGui::DragInt3()@
dragInt3 :: (MonadIO m, HasSetter ref (Int, Int, Int), HasGetter ref (Int, Int, Int)) => Text -> ref -> Float -> Int -> Int -> m Bool
dragInt3 :: forall (m :: * -> *) ref.
(MonadIO m, HasSetter ref (Int, Int, Int),
 HasGetter ref (Int, Int, Int)) =>
Text -> ref -> Float -> Int -> Int -> m Bool
dragInt3 Text
label ref
ref Float
speed Int
minValue Int
maxValue = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (Int
x, Int
y, Int
z) <- ref -> IO (Int, Int, Int)
forall t a (m :: * -> *). (HasGetter t a, MonadIO m) => t -> m a
get ref
ref
  [CInt] -> (Ptr CInt -> IO Bool) -> IO Bool
forall a b. Storable a => [a] -> (Ptr a -> IO b) -> IO b
withArray [ Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
x, Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
y, Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
z ] \Ptr CInt
vPtr -> do
    Bool
changed <-
      Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
label \CString
labelPtr ->
        Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
"%d" \CString
formatPtr ->
          CString
-> Ptr CInt
-> CFloat
-> CInt
-> CInt
-> CString
-> ImGuiSliderFlags
-> IO Bool
forall (m :: * -> *).
MonadIO m =>
CString
-> Ptr CInt
-> CFloat
-> CInt
-> CInt
-> CString
-> ImGuiSliderFlags
-> m Bool
Raw.dragInt3
            CString
labelPtr
            Ptr CInt
vPtr
            (Float -> CFloat
CFloat Float
speed)
            (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
minValue)
            (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
maxValue)
            CString
formatPtr
            ImGuiSliderFlags
ImGuiSliderFlags_AlwaysClamp

    Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
changed do
      [CInt
x', CInt
y', CInt
z'] <- Int -> Ptr CInt -> IO [CInt]
forall a. Storable a => Int -> Ptr a -> IO [a]
peekArray Int
3 Ptr CInt
vPtr
      ref
ref ref -> (Int, Int, Int) -> IO ()
forall t a (m :: * -> *).
(HasSetter t a, MonadIO m) =>
t -> a -> m ()
$=! (CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
x', CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
y', CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
z')

    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
changed

-- | Wraps @ImGui::DragInt4()@
dragInt4 :: (MonadIO m, HasSetter ref (Int, Int, Int, Int), HasGetter ref (Int, Int, Int, Int)) => Text -> ref -> Float -> Int -> Int -> m Bool
dragInt4 :: forall (m :: * -> *) ref.
(MonadIO m, HasSetter ref (Int, Int, Int, Int),
 HasGetter ref (Int, Int, Int, Int)) =>
Text -> ref -> Float -> Int -> Int -> m Bool
dragInt4 Text
label ref
ref Float
speed Int
minValue Int
maxValue = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (Int
x, Int
y, Int
z, Int
w) <- ref -> IO (Int, Int, Int, Int)
forall t a (m :: * -> *). (HasGetter t a, MonadIO m) => t -> m a
get ref
ref
  [CInt] -> (Ptr CInt -> IO Bool) -> IO Bool
forall a b. Storable a => [a] -> (Ptr a -> IO b) -> IO b
withArray [ Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
x, Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
y, Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
z, Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
w ] \Ptr CInt
vPtr -> do
    Bool
changed <-
      Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
label \CString
labelPtr ->
        Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
"%d" \CString
formatPtr ->
          CString
-> Ptr CInt
-> CFloat
-> CInt
-> CInt
-> CString
-> ImGuiSliderFlags
-> IO Bool
forall (m :: * -> *).
MonadIO m =>
CString
-> Ptr CInt
-> CFloat
-> CInt
-> CInt
-> CString
-> ImGuiSliderFlags
-> m Bool
Raw.dragInt4
            CString
labelPtr
            Ptr CInt
vPtr
            (Float -> CFloat
CFloat Float
speed)
            (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
minValue)
            (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
maxValue)
            CString
formatPtr
            ImGuiSliderFlags
ImGuiSliderFlags_AlwaysClamp

    Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
changed do
      [CInt
x', CInt
y', CInt
z', CInt
w'] <- Int -> Ptr CInt -> IO [CInt]
forall a. Storable a => Int -> Ptr a -> IO [a]
peekArray Int
3 Ptr CInt
vPtr
      ref
ref ref -> (Int, Int, Int, Int) -> IO ()
forall t a (m :: * -> *).
(HasSetter t a, MonadIO m) =>
t -> a -> m ()
$=! (CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
x', CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
y', CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
z', CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
w')

    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
changed

dragIntRange2 :: (MonadIO m, HasSetter ref Int, HasGetter ref Int) => Text -> ref -> ref -> Float -> Int -> Int -> Text -> Text -> m Bool
dragIntRange2 :: forall (m :: * -> *) ref.
(MonadIO m, HasSetter ref Int, HasGetter ref Int) =>
Text -> ref -> ref -> Float -> Int -> Int -> Text -> Text -> m Bool
dragIntRange2 Text
desc ref
refMin ref
refMax Float
speed Int
minValue Int
maxValue Text
minFmt Text
maxFmt = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  Int
curMin <- ref -> IO Int
forall t a (m :: * -> *). (HasGetter t a, MonadIO m) => t -> m a
get ref
refMin
  Int
curMax <- ref -> IO Int
forall t a (m :: * -> *). (HasGetter t a, MonadIO m) => t -> m a
get ref
refMax
  CInt -> (Ptr CInt -> IO Bool) -> IO Bool
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
curMin) \Ptr CInt
minPtr ->
    CInt -> (Ptr CInt -> IO Bool) -> IO Bool
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
curMax) \Ptr CInt
maxPtr -> do
      Bool
changed <-
        Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
desc \CString
descPtr ->
          Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
minFmt \CString
minFmtPtr ->
            Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
maxFmt \CString
maxFmtPtr ->
              CString
-> Ptr CInt
-> Ptr CInt
-> CFloat
-> CInt
-> CInt
-> CString
-> CString
-> ImGuiSliderFlags
-> IO Bool
forall (m :: * -> *).
MonadIO m =>
CString
-> Ptr CInt
-> Ptr CInt
-> CFloat
-> CInt
-> CInt
-> CString
-> CString
-> ImGuiSliderFlags
-> m Bool
Raw.dragIntRange2
                CString
descPtr
                Ptr CInt
minPtr
                Ptr CInt
maxPtr
                (Float -> CFloat
CFloat Float
speed)
                (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
minValue)
                (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
maxValue)
                CString
minFmtPtr CString
maxFmtPtr
                ImGuiSliderFlags
ImGuiSliderFlags_AlwaysClamp

      Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
changed do
        CInt
nextMin <- Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek Ptr CInt
minPtr
        CInt
nextMax <- Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek Ptr CInt
maxPtr
        ref
refMin ref -> Int -> IO ()
forall t a (m :: * -> *).
(HasSetter t a, MonadIO m) =>
t -> a -> m ()
$=! CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
nextMin
        ref
refMax ref -> Int -> IO ()
forall t a (m :: * -> *).
(HasSetter t a, MonadIO m) =>
t -> a -> m ()
$=! CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
nextMax

      Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
changed

dragScalar
  :: (HasSetter ref a, HasGetter ref a, HasGetter range a, Storable a, MonadIO m)
  => Text -> ImGuiDataType -> ref -> Float -> range -> range -> Text -> ImGuiSliderFlags -> m Bool
dragScalar :: forall ref a range (m :: * -> *).
(HasSetter ref a, HasGetter ref a, HasGetter range a, Storable a,
 MonadIO m) =>
Text
-> ImGuiDataType
-> ref
-> Float
-> range
-> range
-> Text
-> ImGuiSliderFlags
-> m Bool
dragScalar Text
label ImGuiDataType
dataType ref
ref Float
vSpeed range
refMin range
refMax Text
format ImGuiSliderFlags
flags = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  a
currentValue <- ref -> IO a
forall t a (m :: * -> *). (HasGetter t a, MonadIO m) => t -> m a
get ref
ref
  a
minValue <- range -> IO a
forall t a (m :: * -> *). (HasGetter t a, MonadIO m) => t -> m a
get range
refMin
  a
maxValue <- range -> IO a
forall t a (m :: * -> *). (HasGetter t a, MonadIO m) => t -> m a
get range
refMax

  a -> (Ptr a -> IO Bool) -> IO Bool
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with a
currentValue \Ptr a
dataPtr ->
    a -> (Ptr a -> IO Bool) -> IO Bool
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with a
minValue \Ptr a
minPtr ->
      a -> (Ptr a -> IO Bool) -> IO Bool
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with a
maxValue \Ptr a
maxPtr -> do
        Bool
changed <-
          Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
label \CString
labelPtr ->
            Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
format \CString
formatPtr ->
              CString
-> ImGuiDataType
-> Ptr a
-> CFloat
-> Ptr a
-> Ptr a
-> CString
-> ImGuiSliderFlags
-> IO Bool
forall (m :: * -> *) a.
MonadIO m =>
CString
-> ImGuiDataType
-> Ptr a
-> CFloat
-> Ptr a
-> Ptr a
-> CString
-> ImGuiSliderFlags
-> m Bool
Raw.dragScalar
                CString
labelPtr
                ImGuiDataType
dataType
                Ptr a
dataPtr
                (Float -> CFloat
CFloat Float
vSpeed)
                Ptr a
minPtr
                Ptr a
maxPtr
                CString
formatPtr
                ImGuiSliderFlags
flags

        Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
changed do
          a
newValue <- Ptr a -> IO a
forall a. Storable a => Ptr a -> IO a
peek Ptr a
dataPtr
          ref
ref ref -> a -> IO ()
forall t a (m :: * -> *).
(HasSetter t a, MonadIO m) =>
t -> a -> m ()
$=! a
newValue

        Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
changed

dragScalarN
  :: (HasSetter ref [a], HasGetter ref [a], HasGetter range a, Storable a, MonadIO m)
  => Text -> ImGuiDataType -> ref -> Float -> range -> range -> Text -> ImGuiSliderFlags -> m Bool
dragScalarN :: forall ref a range (m :: * -> *).
(HasSetter ref [a], HasGetter ref [a], HasGetter range a,
 Storable a, MonadIO m) =>
Text
-> ImGuiDataType
-> ref
-> Float
-> range
-> range
-> Text
-> ImGuiSliderFlags
-> m Bool
dragScalarN Text
label ImGuiDataType
dataType ref
ref Float
vSpeed range
refMin range
refMax Text
format ImGuiSliderFlags
flags = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [a]
currentValues <- ref -> IO [a]
forall t a (m :: * -> *). (HasGetter t a, MonadIO m) => t -> m a
get ref
ref
  a
minValue <- range -> IO a
forall t a (m :: * -> *). (HasGetter t a, MonadIO m) => t -> m a
get range
refMin
  a
maxValue <- range -> IO a
forall t a (m :: * -> *). (HasGetter t a, MonadIO m) => t -> m a
get range
refMax

  [a] -> (Int -> Ptr a -> IO Bool) -> IO Bool
forall a b. Storable a => [a] -> (Int -> Ptr a -> IO b) -> IO b
withArrayLen [a]
currentValues \Int
components Ptr a
dataPtr ->
    a -> (Ptr a -> IO Bool) -> IO Bool
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with a
minValue \Ptr a
minPtr ->
      a -> (Ptr a -> IO Bool) -> IO Bool
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with a
maxValue \Ptr a
maxPtr -> do
        Bool
changed <-
          Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
label \CString
labelPtr ->
            Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
format \CString
formatPtr ->
              CString
-> ImGuiDataType
-> Ptr a
-> CInt
-> CFloat
-> Ptr a
-> Ptr a
-> CString
-> ImGuiSliderFlags
-> IO Bool
forall (m :: * -> *) a.
MonadIO m =>
CString
-> ImGuiDataType
-> Ptr a
-> CInt
-> CFloat
-> Ptr a
-> Ptr a
-> CString
-> ImGuiSliderFlags
-> m Bool
Raw.dragScalarN
                CString
labelPtr
                ImGuiDataType
dataType
                Ptr a
dataPtr
                (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
components)
                (Float -> CFloat
CFloat Float
vSpeed)
                Ptr a
minPtr
                Ptr a
maxPtr
                CString
formatPtr
                ImGuiSliderFlags
flags

        Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
changed do
          [a]
newValue <- Int -> Ptr a -> IO [a]
forall a. Storable a => Int -> Ptr a -> IO [a]
peekArray Int
components Ptr a
dataPtr
          ref
ref ref -> [a] -> IO ()
forall t a (m :: * -> *).
(HasSetter t a, MonadIO m) =>
t -> a -> m ()
$=! [a]
newValue

        Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
changed

sliderScalar
  :: (HasGetter ref a, HasSetter ref a, HasGetter range a, Storable a, MonadIO m)
  => Text -> ImGuiDataType -> ref -> range -> range -> Text -> ImGuiSliderFlags -> m Bool
sliderScalar :: forall ref a range (m :: * -> *).
(HasGetter ref a, HasSetter ref a, HasGetter range a, Storable a,
 MonadIO m) =>
Text
-> ImGuiDataType
-> ref
-> range
-> range
-> Text
-> ImGuiSliderFlags
-> m Bool
sliderScalar Text
label ImGuiDataType
dataType ref
ref range
refMin range
refMax Text
format ImGuiSliderFlags
flags = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  a
currentValue <- ref -> IO a
forall t a (m :: * -> *). (HasGetter t a, MonadIO m) => t -> m a
get ref
ref
  a
minValue <- range -> IO a
forall t a (m :: * -> *). (HasGetter t a, MonadIO m) => t -> m a
get range
refMin
  a
maxValue <- range -> IO a
forall t a (m :: * -> *). (HasGetter t a, MonadIO m) => t -> m a
get range
refMax

  a -> (Ptr a -> IO Bool) -> IO Bool
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with a
currentValue \Ptr a
dataPtr ->
    a -> (Ptr a -> IO Bool) -> IO Bool
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with a
minValue \Ptr a
minPtr ->
      a -> (Ptr a -> IO Bool) -> IO Bool
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with a
maxValue \Ptr a
maxPtr -> do
        Bool
changed <-
          Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
label \CString
labelPtr ->
            Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
format \CString
formatPtr ->
              CString
-> ImGuiDataType
-> Ptr a
-> Ptr a
-> Ptr a
-> CString
-> ImGuiSliderFlags
-> IO Bool
forall (m :: * -> *) a.
MonadIO m =>
CString
-> ImGuiDataType
-> Ptr a
-> Ptr a
-> Ptr a
-> CString
-> ImGuiSliderFlags
-> m Bool
Raw.sliderScalar
                CString
labelPtr
                ImGuiDataType
dataType
                Ptr a
dataPtr
                Ptr a
minPtr
                Ptr a
maxPtr
                CString
formatPtr
                ImGuiSliderFlags
flags

        Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
changed do
          a
newValue <- Ptr a -> IO a
forall a. Storable a => Ptr a -> IO a
peek Ptr a
dataPtr
          ref
ref ref -> a -> IO ()
forall t a (m :: * -> *).
(HasSetter t a, MonadIO m) =>
t -> a -> m ()
$=! a
newValue

        Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
changed

sliderScalarN
  :: (HasSetter value [a], HasGetter value [a], HasGetter range a, Storable a, MonadIO m)
  => Text -> ImGuiDataType -> value -> range -> range -> Text -> ImGuiSliderFlags -> m Bool
sliderScalarN :: forall value a range (m :: * -> *).
(HasSetter value [a], HasGetter value [a], HasGetter range a,
 Storable a, MonadIO m) =>
Text
-> ImGuiDataType
-> value
-> range
-> range
-> Text
-> ImGuiSliderFlags
-> m Bool
sliderScalarN Text
label ImGuiDataType
dataType value
ref range
refMin range
refMax Text
format ImGuiSliderFlags
flags = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  [a]
currentValues <- value -> IO [a]
forall t a (m :: * -> *). (HasGetter t a, MonadIO m) => t -> m a
get value
ref
  a
minValue <- range -> IO a
forall t a (m :: * -> *). (HasGetter t a, MonadIO m) => t -> m a
get range
refMin
  a
maxValue <- range -> IO a
forall t a (m :: * -> *). (HasGetter t a, MonadIO m) => t -> m a
get range
refMax

  [a] -> (Int -> Ptr a -> IO Bool) -> IO Bool
forall a b. Storable a => [a] -> (Int -> Ptr a -> IO b) -> IO b
withArrayLen [a]
currentValues \Int
components Ptr a
dataPtr ->
    a -> (Ptr a -> IO Bool) -> IO Bool
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with a
minValue \Ptr a
minPtr ->
      a -> (Ptr a -> IO Bool) -> IO Bool
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with a
maxValue \Ptr a
maxPtr -> do
        Bool
changed <-
          Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
label \CString
labelPtr ->
            Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
format \CString
formatPtr ->
              CString
-> ImGuiDataType
-> Ptr a
-> CInt
-> Ptr a
-> Ptr a
-> CString
-> ImGuiSliderFlags
-> IO Bool
forall (m :: * -> *) a.
MonadIO m =>
CString
-> ImGuiDataType
-> Ptr a
-> CInt
-> Ptr a
-> Ptr a
-> CString
-> ImGuiSliderFlags
-> m Bool
Raw.sliderScalarN
                CString
labelPtr
                ImGuiDataType
dataType
                Ptr a
dataPtr
                (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
components)
                Ptr a
minPtr
                Ptr a
maxPtr
                CString
formatPtr
                ImGuiSliderFlags
flags

        Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
changed do
          [a]
newValue <- Int -> Ptr a -> IO [a]
forall a. Storable a => Int -> Ptr a -> IO [a]
peekArray Int
components Ptr a
dataPtr
          value
ref value -> [a] -> IO ()
forall t a (m :: * -> *).
(HasSetter t a, MonadIO m) =>
t -> a -> m ()
$=! [a]
newValue

        Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
changed

-- | Wraps @ImGui::SliderFloat()@
sliderFloat :: (MonadIO m, HasSetter ref Float, HasGetter ref Float) => Text -> ref -> Float -> Float -> m Bool
sliderFloat :: forall (m :: * -> *) ref.
(MonadIO m, HasSetter ref Float, HasGetter ref Float) =>
Text -> ref -> Float -> Float -> m Bool
sliderFloat Text
desc ref
ref Float
minValue Float
maxValue = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  Float
currentValue <- ref -> IO Float
forall t a (m :: * -> *). (HasGetter t a, MonadIO m) => t -> m a
get ref
ref
  CFloat -> (Ptr CFloat -> IO Bool) -> IO Bool
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with (Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
currentValue) \Ptr CFloat
floatPtr -> do
    Bool
changed <- Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
desc \CString
descPtr ->
      CString -> Ptr CFloat -> CFloat -> CFloat -> IO Bool
forall (m :: * -> *).
MonadIO m =>
CString -> Ptr CFloat -> CFloat -> CFloat -> m Bool
Raw.sliderFloat CString
descPtr Ptr CFloat
floatPtr (Float -> CFloat
CFloat Float
minValue) (Float -> CFloat
CFloat Float
maxValue)

    Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
changed do
      CFloat
newValue <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek Ptr CFloat
floatPtr
      ref
ref ref -> Float -> IO ()
forall t a (m :: * -> *).
(HasSetter t a, MonadIO m) =>
t -> a -> m ()
$=! CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
newValue

    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
changed

-- | Wraps @ImGui::SliderFloat2()@
sliderFloat2 :: (MonadIO m, HasSetter ref (Float, Float), HasGetter ref (Float, Float)) => Text -> ref -> Float -> Float -> m Bool
sliderFloat2 :: forall (m :: * -> *) ref.
(MonadIO m, HasSetter ref (Float, Float),
 HasGetter ref (Float, Float)) =>
Text -> ref -> Float -> Float -> m Bool
sliderFloat2 Text
desc ref
ref Float
minValue Float
maxValue = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (Float
x, Float
y) <- ref -> IO (Float, Float)
forall t a (m :: * -> *). (HasGetter t a, MonadIO m) => t -> m a
get ref
ref
  [CFloat] -> (Ptr CFloat -> IO Bool) -> IO Bool
forall a b. Storable a => [a] -> (Ptr a -> IO b) -> IO b
withArray [ Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
x, Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
y ] \Ptr CFloat
floatPtr -> do
    Bool
changed <- Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
desc \CString
descPtr ->
      CString -> Ptr CFloat -> CFloat -> CFloat -> IO Bool
forall (m :: * -> *).
MonadIO m =>
CString -> Ptr CFloat -> CFloat -> CFloat -> m Bool
Raw.sliderFloat CString
descPtr Ptr CFloat
floatPtr (Float -> CFloat
CFloat Float
minValue) (Float -> CFloat
CFloat Float
maxValue)

    Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
changed do
      [CFloat
x', CFloat
y'] <- Int -> Ptr CFloat -> IO [CFloat]
forall a. Storable a => Int -> Ptr a -> IO [a]
peekArray Int
2 Ptr CFloat
floatPtr
      ref
ref ref -> (Float, Float) -> IO ()
forall t a (m :: * -> *).
(HasSetter t a, MonadIO m) =>
t -> a -> m ()
$=! (CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
x', CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
y')

    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
changed

-- | Wraps @ImGui::SliderFloat3()@
sliderFloat3 :: (MonadIO m, HasSetter ref (Float, Float, Float), HasGetter ref (Float, Float, Float)) => Text -> ref -> Float -> Float -> m Bool
sliderFloat3 :: forall (m :: * -> *) ref.
(MonadIO m, HasSetter ref (Float, Float, Float),
 HasGetter ref (Float, Float, Float)) =>
Text -> ref -> Float -> Float -> m Bool
sliderFloat3 Text
desc ref
ref Float
minValue Float
maxValue = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (Float
x, Float
y, Float
z) <- ref -> IO (Float, Float, Float)
forall t a (m :: * -> *). (HasGetter t a, MonadIO m) => t -> m a
get ref
ref
  [CFloat] -> (Ptr CFloat -> IO Bool) -> IO Bool
forall a b. Storable a => [a] -> (Ptr a -> IO b) -> IO b
withArray [ Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
x, Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
y, Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
z ] \Ptr CFloat
floatPtr -> do
    Bool
changed <- Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
desc \CString
descPtr ->
      CString -> Ptr CFloat -> CFloat -> CFloat -> IO Bool
forall (m :: * -> *).
MonadIO m =>
CString -> Ptr CFloat -> CFloat -> CFloat -> m Bool
Raw.sliderFloat CString
descPtr Ptr CFloat
floatPtr (Float -> CFloat
CFloat Float
minValue) (Float -> CFloat
CFloat Float
maxValue)

    Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
changed do
      [CFloat
x', CFloat
y', CFloat
z'] <- Int -> Ptr CFloat -> IO [CFloat]
forall a. Storable a => Int -> Ptr a -> IO [a]
peekArray Int
3 Ptr CFloat
floatPtr
      ref
ref ref -> (Float, Float, Float) -> IO ()
forall t a (m :: * -> *).
(HasSetter t a, MonadIO m) =>
t -> a -> m ()
$=! (CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
x', CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
y', CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
z')

    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
changed

-- | Wraps @ImGui::SliderFloat4()@
sliderFloat4 :: (MonadIO m, HasSetter ref (Float, Float, Float, Float), HasGetter ref (Float, Float, Float, Float)) => Text -> ref -> Float -> Float -> m Bool
sliderFloat4 :: forall (m :: * -> *) ref.
(MonadIO m, HasSetter ref (Float, Float, Float, Float),
 HasGetter ref (Float, Float, Float, Float)) =>
Text -> ref -> Float -> Float -> m Bool
sliderFloat4 Text
desc ref
ref Float
minValue Float
maxValue = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (Float
x, Float
y, Float
z, Float
u) <- ref -> IO (Float, Float, Float, Float)
forall t a (m :: * -> *). (HasGetter t a, MonadIO m) => t -> m a
get ref
ref
  [CFloat] -> (Ptr CFloat -> IO Bool) -> IO Bool
forall a b. Storable a => [a] -> (Ptr a -> IO b) -> IO b
withArray [ Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
x, Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
y, Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
z, Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
u ] \Ptr CFloat
floatPtr -> do
    Bool
changed <- Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
desc \CString
descPtr ->
      CString -> Ptr CFloat -> CFloat -> CFloat -> IO Bool
forall (m :: * -> *).
MonadIO m =>
CString -> Ptr CFloat -> CFloat -> CFloat -> m Bool
Raw.sliderFloat CString
descPtr Ptr CFloat
floatPtr (Float -> CFloat
CFloat Float
minValue) (Float -> CFloat
CFloat Float
maxValue)

    Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
changed do
      [CFloat
x', CFloat
y', CFloat
z', CFloat
u'] <- Int -> Ptr CFloat -> IO [CFloat]
forall a. Storable a => Int -> Ptr a -> IO [a]
peekArray Int
4 Ptr CFloat
floatPtr
      ref
ref ref -> (Float, Float, Float, Float) -> IO ()
forall t a (m :: * -> *).
(HasSetter t a, MonadIO m) =>
t -> a -> m ()
$=! (CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
x', CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
y', CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
z', CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
u')

    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
changed

-- | Slider widget to select an angle in radians, while displaying degrees.
sliderAngle :: (MonadIO m, HasSetter ref Float, HasGetter ref Float) => Text -> ref -> Float -> Float -> m Bool
sliderAngle :: forall (m :: * -> *) ref.
(MonadIO m, HasSetter ref Float, HasGetter ref Float) =>
Text -> ref -> Float -> Float -> m Bool
sliderAngle Text
desc ref
refRads Float
minDegs Float
maxDegs = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  Float
currentRads <- ref -> IO Float
forall t a (m :: * -> *). (HasGetter t a, MonadIO m) => t -> m a
get ref
refRads
  CFloat -> (Ptr CFloat -> IO Bool) -> IO Bool
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with (Float -> CFloat
CFloat Float
currentRads) \Ptr CFloat
currentRadsPtr -> do
    Bool
changed <-
      Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
desc \CString
descPtr ->
        Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
"%.0f deg" \CString
formatPtr ->
          CString
-> Ptr CFloat
-> CFloat
-> CFloat
-> CString
-> ImGuiSliderFlags
-> IO Bool
forall (m :: * -> *).
MonadIO m =>
CString
-> Ptr CFloat
-> CFloat
-> CFloat
-> CString
-> ImGuiSliderFlags
-> m Bool
Raw.sliderAngle CString
descPtr Ptr CFloat
currentRadsPtr (Float -> CFloat
CFloat Float
minDegs) (Float -> CFloat
CFloat Float
maxDegs) CString
formatPtr ImGuiSliderFlags
ImGuiSliderFlags_AlwaysClamp

    Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
changed do
      CFloat Float
newRads <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek Ptr CFloat
currentRadsPtr
      ref
refRads ref -> Float -> IO ()
forall t a (m :: * -> *).
(HasSetter t a, MonadIO m) =>
t -> a -> m ()
$=! Float
newRads

    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
changed

-- | Wraps @ImGui::SliderInt()@
sliderInt
  :: (MonadIO m, HasSetter ref Int, HasGetter ref Int)
  => Text -> ref -> Int -> Int -> m Bool
sliderInt :: forall (m :: * -> *) ref.
(MonadIO m, HasSetter ref Int, HasGetter ref Int) =>
Text -> ref -> Int -> Int -> m Bool
sliderInt Text
label ref
ref Int
minValue Int
maxValue = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  Int
currentValue <- ref -> IO Int
forall t a (m :: * -> *). (HasGetter t a, MonadIO m) => t -> m a
get ref
ref
  CInt -> (Ptr CInt -> IO Bool) -> IO Bool
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
currentValue) \Ptr CInt
vPtr -> do
    Bool
changed <-
      Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
label \CString
labelPtr ->
        Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
"%d" \CString
formatPtr ->
          CString
-> Ptr CInt
-> CInt
-> CInt
-> CString
-> ImGuiSliderFlags
-> IO Bool
forall (m :: * -> *).
MonadIO m =>
CString
-> Ptr CInt
-> CInt
-> CInt
-> CString
-> ImGuiSliderFlags
-> m Bool
Raw.sliderInt
            CString
labelPtr
            Ptr CInt
vPtr
            (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
minValue)
            (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
maxValue)
            CString
formatPtr
            ImGuiSliderFlags
ImGuiSliderFlags_AlwaysClamp

    Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
changed do
      CInt
newValue <- Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek Ptr CInt
vPtr
      ref
ref ref -> Int -> IO ()
forall t a (m :: * -> *).
(HasSetter t a, MonadIO m) =>
t -> a -> m ()
$=! CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
newValue

    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
changed

-- | Wraps @ImGui::SliderInt2()@
sliderInt2
  :: (MonadIO m, HasSetter ref (Int, Int), HasGetter ref (Int, Int))
  => Text -> ref -> Int -> Int -> m Bool
sliderInt2 :: forall (m :: * -> *) ref.
(MonadIO m, HasSetter ref (Int, Int), HasGetter ref (Int, Int)) =>
Text -> ref -> Int -> Int -> m Bool
sliderInt2 Text
label ref
ref Int
minValue Int
maxValue = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (Int
x, Int
y) <- ref -> IO (Int, Int)
forall t a (m :: * -> *). (HasGetter t a, MonadIO m) => t -> m a
get ref
ref
  [CInt] -> (Ptr CInt -> IO Bool) -> IO Bool
forall a b. Storable a => [a] -> (Ptr a -> IO b) -> IO b
withArray [ Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
x, Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
y ] \Ptr CInt
vPtr -> do
    Bool
changed <-
      Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
label \CString
labelPtr ->
        Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
"%d" \CString
formatPtr ->
          CString
-> Ptr CInt
-> CInt
-> CInt
-> CString
-> ImGuiSliderFlags
-> IO Bool
forall (m :: * -> *).
MonadIO m =>
CString
-> Ptr CInt
-> CInt
-> CInt
-> CString
-> ImGuiSliderFlags
-> m Bool
Raw.sliderInt2
            CString
labelPtr
            Ptr CInt
vPtr
            (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
minValue)
            (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
maxValue)
            CString
formatPtr
            ImGuiSliderFlags
ImGuiSliderFlags_AlwaysClamp

    Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
changed do
      [CInt
x', CInt
y'] <- Int -> Ptr CInt -> IO [CInt]
forall a. Storable a => Int -> Ptr a -> IO [a]
peekArray Int
2 Ptr CInt
vPtr
      ref
ref ref -> (Int, Int) -> IO ()
forall t a (m :: * -> *).
(HasSetter t a, MonadIO m) =>
t -> a -> m ()
$=! (CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
x', CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
y')

    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
changed

-- | Wraps @ImGui::SliderInt3()@
sliderInt3
  :: (MonadIO m, HasSetter ref (Int, Int, Int), HasGetter ref (Int, Int, Int))
  => Text -> ref -> Int -> Int -> m Bool
sliderInt3 :: forall (m :: * -> *) ref.
(MonadIO m, HasSetter ref (Int, Int, Int),
 HasGetter ref (Int, Int, Int)) =>
Text -> ref -> Int -> Int -> m Bool
sliderInt3 Text
label ref
ref Int
minValue Int
maxValue = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (Int
x, Int
y, Int
z) <- ref -> IO (Int, Int, Int)
forall t a (m :: * -> *). (HasGetter t a, MonadIO m) => t -> m a
get ref
ref
  [CInt] -> (Ptr CInt -> IO Bool) -> IO Bool
forall a b. Storable a => [a] -> (Ptr a -> IO b) -> IO b
withArray [ Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
x, Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
y, Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
z ] \Ptr CInt
vPtr -> do
    Bool
changed <-
      Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
label \CString
labelPtr ->
        Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
"%d" \CString
formatPtr ->
          CString
-> Ptr CInt
-> CInt
-> CInt
-> CString
-> ImGuiSliderFlags
-> IO Bool
forall (m :: * -> *).
MonadIO m =>
CString
-> Ptr CInt
-> CInt
-> CInt
-> CString
-> ImGuiSliderFlags
-> m Bool
Raw.sliderInt3
            CString
labelPtr
            Ptr CInt
vPtr
            (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
minValue)
            (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
maxValue)
            CString
formatPtr
            ImGuiSliderFlags
ImGuiSliderFlags_AlwaysClamp

    Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
changed do
      [CInt
x', CInt
y', CInt
z'] <- Int -> Ptr CInt -> IO [CInt]
forall a. Storable a => Int -> Ptr a -> IO [a]
peekArray Int
3 Ptr CInt
vPtr
      ref
ref ref -> (Int, Int, Int) -> IO ()
forall t a (m :: * -> *).
(HasSetter t a, MonadIO m) =>
t -> a -> m ()
$=! (CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
x', CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
y', CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
z')

    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
changed

-- | Wraps @ImGui::SliderInt4()@
sliderInt4
  :: (MonadIO m, HasSetter ref (Int, Int, Int, Int), HasGetter ref (Int, Int, Int, Int))
  => Text -> ref -> Int -> Int -> m Bool
sliderInt4 :: forall (m :: * -> *) ref.
(MonadIO m, HasSetter ref (Int, Int, Int, Int),
 HasGetter ref (Int, Int, Int, Int)) =>
Text -> ref -> Int -> Int -> m Bool
sliderInt4 Text
label ref
ref Int
minValue Int
maxValue = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  (Int
x, Int
y, Int
z, Int
w) <- ref -> IO (Int, Int, Int, Int)
forall t a (m :: * -> *). (HasGetter t a, MonadIO m) => t -> m a
get ref
ref
  [CInt] -> (Ptr CInt -> IO Bool) -> IO Bool
forall a b. Storable a => [a] -> (Ptr a -> IO b) -> IO b
withArray [ Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
x, Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
y, Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
z, Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
w] \Ptr CInt
vPtr -> do
    Bool
changed <-
      Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
label \CString
labelPtr ->
        Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
"%d" \CString
formatPtr ->
          CString
-> Ptr CInt
-> CInt
-> CInt
-> CString
-> ImGuiSliderFlags
-> IO Bool
forall (m :: * -> *).
MonadIO m =>
CString
-> Ptr CInt
-> CInt
-> CInt
-> CString
-> ImGuiSliderFlags
-> m Bool
Raw.sliderInt4
            CString
labelPtr
            Ptr CInt
vPtr
            (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
minValue)
            (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
maxValue)
            CString
formatPtr
            ImGuiSliderFlags
ImGuiSliderFlags_AlwaysClamp

    Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
changed do
      [CInt
x', CInt
y', CInt
z', CInt
w'] <- Int -> Ptr CInt -> IO [CInt]
forall a. Storable a => Int -> Ptr a -> IO [a]
peekArray Int
4 Ptr CInt
vPtr
      ref
ref ref -> (Int, Int, Int, Int) -> IO ()
forall t a (m :: * -> *).
(HasSetter t a, MonadIO m) =>
t -> a -> m ()
$=! (CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
x', CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
y', CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
z', CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
w')

    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
changed

vSliderFloat
  :: (HasSetter ref Float, HasGetter ref Float, MonadIO m)
  => Text -> ImVec2 -> ref -> Float -> Float -> m Bool
vSliderFloat :: forall ref (m :: * -> *).
(HasSetter ref Float, HasGetter ref Float, MonadIO m) =>
Text -> ImVec2 -> ref -> Float -> Float -> m Bool
vSliderFloat Text
label ImVec2
size ref
ref Float
minValue Float
maxValue = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  Float
currentValue <- ref -> IO Float
forall t a (m :: * -> *). (HasGetter t a, MonadIO m) => t -> m a
get ref
ref

  ImVec2 -> (Ptr ImVec2 -> IO Bool) -> IO Bool
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with ImVec2
size \Ptr ImVec2
sizePtr ->
    CFloat -> (Ptr CFloat -> IO Bool) -> IO Bool
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with (Float -> CFloat
CFloat Float
currentValue) \Ptr CFloat
dataPtr -> do
      Bool
changed <-
        Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
label \CString
labelPtr ->
          Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
"%.3f" \CString
formatPtr ->
            CString
-> Ptr ImVec2
-> Ptr CFloat
-> CFloat
-> CFloat
-> CString
-> ImGuiSliderFlags
-> IO Bool
forall (m :: * -> *).
MonadIO m =>
CString
-> Ptr ImVec2
-> Ptr CFloat
-> CFloat
-> CFloat
-> CString
-> ImGuiSliderFlags
-> m Bool
Raw.vSliderFloat
              CString
labelPtr
              Ptr ImVec2
sizePtr
              Ptr CFloat
dataPtr
              (Float -> CFloat
CFloat Float
minValue)
              (Float -> CFloat
CFloat Float
maxValue)
              CString
formatPtr
              ImGuiSliderFlags
ImGuiSliderFlags_AlwaysClamp

      Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
changed do
        CFloat Float
newValue <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek Ptr CFloat
dataPtr
        ref
ref ref -> Float -> IO ()
forall t a (m :: * -> *).
(HasSetter t a, MonadIO m) =>
t -> a -> m ()
$=! Float
newValue

      Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
changed

vSliderInt
  :: (HasSetter ref Int, HasGetter ref Int, MonadIO m)
  => Text -> ImVec2 -> ref -> Int -> Int -> m Bool
vSliderInt :: forall ref (m :: * -> *).
(HasSetter ref Int, HasGetter ref Int, MonadIO m) =>
Text -> ImVec2 -> ref -> Int -> Int -> m Bool
vSliderInt Text
label ImVec2
size ref
ref Int
minValue Int
maxValue = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  Int
currentValue <- ref -> IO Int
forall t a (m :: * -> *). (HasGetter t a, MonadIO m) => t -> m a
get ref
ref

  ImVec2 -> (Ptr ImVec2 -> IO Bool) -> IO Bool
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with ImVec2
size \Ptr ImVec2
sizePtr ->
    CInt -> (Ptr CInt -> IO Bool) -> IO Bool
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
currentValue) \Ptr CInt
dataPtr -> do
      Bool
changed <-
        Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
label \CString
labelPtr ->
          Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
"%d" \CString
formatPtr ->
            CString
-> Ptr ImVec2
-> Ptr CInt
-> CInt
-> CInt
-> CString
-> ImGuiSliderFlags
-> IO Bool
forall (m :: * -> *).
MonadIO m =>
CString
-> Ptr ImVec2
-> Ptr CInt
-> CInt
-> CInt
-> CString
-> ImGuiSliderFlags
-> m Bool
Raw.vSliderInt
              CString
labelPtr
              Ptr ImVec2
sizePtr
              Ptr CInt
dataPtr
              (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
minValue)
              (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
maxValue)
              CString
formatPtr
              ImGuiSliderFlags
ImGuiSliderFlags_AlwaysClamp

      Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
changed do
        CInt
newValue <- Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek Ptr CInt
dataPtr
        ref
ref ref -> Int -> IO ()
forall t a (m :: * -> *).
(HasSetter t a, MonadIO m) =>
t -> a -> m ()
$=! CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
newValue

      Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
changed

vSliderScalar
  :: (HasSetter ref a, HasGetter ref a, HasGetter range a, Storable a, MonadIO m)
  => Text -> ImVec2 -> ImGuiDataType -> ref -> range -> range -> Text -> ImGuiSliderFlags -> m Bool
vSliderScalar :: forall ref a range (m :: * -> *).
(HasSetter ref a, HasGetter ref a, HasGetter range a, Storable a,
 MonadIO m) =>
Text
-> ImVec2
-> ImGuiDataType
-> ref
-> range
-> range
-> Text
-> ImGuiSliderFlags
-> m Bool
vSliderScalar Text
label ImVec2
size ImGuiDataType
dataType ref
ref range
refMin range
refMax Text
format ImGuiSliderFlags
flags = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  a
currentValue <- ref -> IO a
forall t a (m :: * -> *). (HasGetter t a, MonadIO m) => t -> m a
get ref
ref
  a
minValue <- range -> IO a
forall t a (m :: * -> *). (HasGetter t a, MonadIO m) => t -> m a
get range
refMin
  a
maxValue <- range -> IO a
forall t a (m :: * -> *). (HasGetter t a, MonadIO m) => t -> m a
get range
refMax

  ImVec2 -> (Ptr ImVec2 -> IO Bool) -> IO Bool
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with ImVec2
size \Ptr ImVec2
sizePtr ->
    a -> (Ptr a -> IO Bool) -> IO Bool
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with a
currentValue \Ptr a
dataPtr ->
      a -> (Ptr a -> IO Bool) -> IO Bool
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with a
minValue \Ptr a
minPtr ->
        a -> (Ptr a -> IO Bool) -> IO Bool
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with a
maxValue \Ptr a
maxPtr -> do
          Bool
changed <-
            Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
label \CString
labelPtr ->
              Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
format \CString
formatPtr ->
                CString
-> Ptr ImVec2
-> ImGuiDataType
-> Ptr a
-> Ptr a
-> Ptr a
-> CString
-> ImGuiSliderFlags
-> IO Bool
forall (m :: * -> *) a.
MonadIO m =>
CString
-> Ptr ImVec2
-> ImGuiDataType
-> Ptr a
-> Ptr a
-> Ptr a
-> CString
-> ImGuiSliderFlags
-> m Bool
Raw.vSliderScalar
                  CString
labelPtr
                  Ptr ImVec2
sizePtr
                  ImGuiDataType
dataType
                  Ptr a
dataPtr
                  Ptr a
minPtr
                  Ptr a
maxPtr
                  CString
formatPtr
                  ImGuiSliderFlags
flags

          Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
changed do
            a
newValue <- Ptr a -> IO a
forall a. Storable a => Ptr a -> IO a
peek Ptr a
dataPtr
            ref
ref ref -> a -> IO ()
forall t a (m :: * -> *).
(HasSetter t a, MonadIO m) =>
t -> a -> m ()
$=! a
newValue

          Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
changed


-- | Wraps @ImGui::InputText()@.
inputText :: (MonadIO m, HasSetter ref Text, HasGetter ref Text) => Text -> ref -> Int -> m Bool
inputText :: forall (m :: * -> *) ref.
(MonadIO m, HasSetter ref Text, HasGetter ref Text) =>
Text -> ref -> Int -> m Bool
inputText Text
label ref
ref Int
bufSize =
  ref -> Int -> (CStringLen -> IO Bool) -> m Bool
forall (m :: * -> *) ref.
(MonadIO m, HasSetter ref Text, HasGetter ref Text) =>
ref -> Int -> (CStringLen -> IO Bool) -> m Bool
withInputString ref
ref Int
bufSize \CStringLen
bufPtrLen ->
      Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
label \CString
labelPtr ->
        CString -> CStringLen -> ImGuiInputTextFlags -> IO Bool
forall (m :: * -> *).
MonadIO m =>
CString -> CStringLen -> ImGuiInputTextFlags -> m Bool
Raw.inputText
          CString
labelPtr
          CStringLen
bufPtrLen
          ImGuiInputTextFlags
ImGuiInputTextFlags_None


-- | Wraps @ImGui::InputTextMultiline()@.
inputTextMultiline :: (MonadIO m, HasSetter ref Text, HasGetter ref Text) => Text -> ref -> Int -> ImVec2 -> m Bool
inputTextMultiline :: forall (m :: * -> *) ref.
(MonadIO m, HasSetter ref Text, HasGetter ref Text) =>
Text -> ref -> Int -> ImVec2 -> m Bool
inputTextMultiline Text
label ref
ref Int
bufSize ImVec2
size =
  ref -> Int -> (CStringLen -> IO Bool) -> m Bool
forall (m :: * -> *) ref.
(MonadIO m, HasSetter ref Text, HasGetter ref Text) =>
ref -> Int -> (CStringLen -> IO Bool) -> m Bool
withInputString ref
ref Int
bufSize \CStringLen
bufPtrLen ->
    Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
label \CString
labelPtr ->
      ImVec2 -> (Ptr ImVec2 -> IO Bool) -> IO Bool
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with ImVec2
size \Ptr ImVec2
sizePtr ->
        CString
-> CStringLen -> Ptr ImVec2 -> ImGuiInputTextFlags -> IO Bool
forall (m :: * -> *).
MonadIO m =>
CString
-> CStringLen -> Ptr ImVec2 -> ImGuiInputTextFlags -> m Bool
Raw.inputTextMultiline
          CString
labelPtr
          CStringLen
bufPtrLen
          Ptr ImVec2
sizePtr
          ImGuiInputTextFlags
ImGuiInputTextFlags_None


-- | Wraps @ImGui::InputTextWithHint()@.
inputTextWithHint :: (MonadIO m, HasSetter ref Text, HasGetter ref Text) => Text -> Text -> ref -> Int -> m Bool
inputTextWithHint :: forall (m :: * -> *) ref.
(MonadIO m, HasSetter ref Text, HasGetter ref Text) =>
Text -> Text -> ref -> Int -> m Bool
inputTextWithHint Text
label Text
hint ref
ref Int
bufSize =
  ref -> Int -> (CStringLen -> IO Bool) -> m Bool
forall (m :: * -> *) ref.
(MonadIO m, HasSetter ref Text, HasGetter ref Text) =>
ref -> Int -> (CStringLen -> IO Bool) -> m Bool
withInputString ref
ref Int
bufSize \CStringLen
bufPtrLen ->
    Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
label \CString
labelPtr ->
      Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
hint \CString
hintPtr ->
        CString -> CString -> CStringLen -> ImGuiInputTextFlags -> IO Bool
forall (m :: * -> *).
MonadIO m =>
CString -> CString -> CStringLen -> ImGuiInputTextFlags -> m Bool
Raw.inputTextWithHint
          CString
labelPtr
          CString
hintPtr
          CStringLen
bufPtrLen
          ImGuiInputTextFlags
ImGuiInputTextFlags_None


-- | Internal helper to prepare appropriately sized and encoded input buffer.
withInputString
  :: (MonadIO m, HasSetter ref Text, HasGetter ref Text)
  => ref
  -> Int
  -> (CStringLen -> IO Bool)
  -> m Bool
withInputString :: forall (m :: * -> *) ref.
(MonadIO m, HasSetter ref Text, HasGetter ref Text) =>
ref -> Int -> (CStringLen -> IO Bool) -> m Bool
withInputString ref
ref Int
bufSize CStringLen -> IO Bool
action = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  Text
input <- ref -> IO Text
forall t a (m :: * -> *). (HasGetter t a, MonadIO m) => t -> m a
get ref
ref
  Text -> (CStringLen -> IO Bool) -> IO Bool
forall a. Text -> (CStringLen -> IO a) -> IO a
Text.withCStringLen Text
input \(CString
refPtr, Int
refSize) ->
    -- XXX: Allocate and zero buffer to receive imgui updates.
    IO CString -> (CString -> IO ()) -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a b c.
MonadUnliftIO m =>
m a -> (a -> m b) -> (a -> m c) -> m c
bracket (Int -> IO CString
forall {a}. Int -> IO (Ptr a)
mkBuf Int
refSize) CString -> IO ()
forall a. Ptr a -> IO ()
free \CString
bufPtr -> do
      -- XXX: Copy the original input.
      CString -> CString -> Int -> IO ()
forall a. Ptr a -> Ptr a -> Int -> IO ()
copyBytes CString
bufPtr CString
refPtr Int
refSize

      Bool
changed <- CStringLen -> IO Bool
action (CString
bufPtr, Int
bufSize)

      Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
changed do
        -- XXX: Assuming Imgui wouldn't write over the bump stop so peekCString would finish.
        Text
newValue <- CString -> IO Text
Text.peekCString CString
bufPtr
        ref
ref ref -> Text -> IO ()
forall t a (m :: * -> *).
(HasSetter t a, MonadIO m) =>
t -> a -> m ()
$=! Text
newValue

      Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
changed
  where
    mkBuf :: Int -> IO (Ptr a)
mkBuf Int
refSize =
      Int -> IO (Ptr a)
forall {a}. Int -> IO (Ptr a)
callocBytes (Int -> IO (Ptr a)) -> Int -> IO (Ptr a)
forall a b. (a -> b) -> a -> b
$
        Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
refSize Int
bufSize Int -> Int -> Int
forall a. Num a => a -> a -> a
+
        Int
5 -- XXX: max size of UTF8 code point + NUL terminator


-- | Wraps @ImGui::ColorPicker3()@.
colorPicker3 :: (MonadIO m, HasSetter ref ImVec3, HasGetter ref ImVec3) => Text -> ref -> m Bool
colorPicker3 :: forall (m :: * -> *) ref.
(MonadIO m, HasSetter ref ImVec3, HasGetter ref ImVec3) =>
Text -> ref -> m Bool
colorPicker3 Text
desc ref
ref = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  ImVec3{Float
$sel:x:ImVec3 :: ImVec3 -> Float
x :: Float
x, Float
$sel:y:ImVec3 :: ImVec3 -> Float
y :: Float
y, Float
$sel:z:ImVec3 :: ImVec3 -> Float
z :: Float
z} <- ref -> IO ImVec3
forall t a (m :: * -> *). (HasGetter t a, MonadIO m) => t -> m a
get ref
ref
  [CFloat] -> (Ptr CFloat -> IO Bool) -> IO Bool
forall a b. Storable a => [a] -> (Ptr a -> IO b) -> IO b
withArray (Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac (Float -> CFloat) -> [Float] -> [CFloat]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Float
x, Float
y, Float
z]) \Ptr CFloat
refPtr -> do
    Bool
changed <- Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
desc \CString
descPtr ->
      CString -> Ptr CFloat -> IO Bool
forall (m :: * -> *). MonadIO m => CString -> Ptr CFloat -> m Bool
Raw.colorPicker3 CString
descPtr Ptr CFloat
refPtr

    Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
changed do
      [CFloat
x', CFloat
y', CFloat
z'] <- Int -> Ptr CFloat -> IO [CFloat]
forall a. Storable a => Int -> Ptr a -> IO [a]
peekArray Int
3 Ptr CFloat
refPtr
      ref
ref ref -> ImVec3 -> IO ()
forall t a (m :: * -> *).
(HasSetter t a, MonadIO m) =>
t -> a -> m ()
$=! Float -> Float -> Float -> ImVec3
ImVec3 (CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
x') (CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
y') (CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
z')

    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
changed


-- | Display a color square/button, hover for details, return true when pressed.
--
-- Wraps @ImGui::ColorButton()@.
colorButton :: (MonadIO m, HasSetter ref ImVec4, HasGetter ref ImVec4) => Text -> ref -> m Bool
colorButton :: forall (m :: * -> *) ref.
(MonadIO m, HasSetter ref ImVec4, HasGetter ref ImVec4) =>
Text -> ref -> m Bool
colorButton Text
desc ref
ref = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  ImVec4
currentValue <- ref -> IO ImVec4
forall t a (m :: * -> *). (HasGetter t a, MonadIO m) => t -> m a
get ref
ref
  ImVec4 -> (Ptr ImVec4 -> IO Bool) -> IO Bool
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with ImVec4
currentValue \Ptr ImVec4
refPtr -> do
    Bool
changed <- Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
desc \CString
descPtr ->
      CString -> Ptr ImVec4 -> IO Bool
forall (m :: * -> *). MonadIO m => CString -> Ptr ImVec4 -> m Bool
Raw.colorButton CString
descPtr Ptr ImVec4
refPtr

    Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
changed do
      ImVec4
newValue <- Ptr ImVec4 -> IO ImVec4
forall a. Storable a => Ptr a -> IO a
peek Ptr ImVec4
refPtr
      ref
ref ref -> ImVec4 -> IO ()
forall t a (m :: * -> *).
(HasSetter t a, MonadIO m) =>
t -> a -> m ()
$=! ImVec4
newValue

    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
changed

data TableOptions = TableOptions
  { TableOptions -> ImGuiTableFlags
tableFlags      :: ImGuiTableFlags
  , TableOptions -> ImVec2
tableOuterSize  :: ImVec2
  , TableOptions -> Float
tableInnerWidth :: Float
  } deriving Int -> TableOptions -> ShowS
[TableOptions] -> ShowS
TableOptions -> String
(Int -> TableOptions -> ShowS)
-> (TableOptions -> String)
-> ([TableOptions] -> ShowS)
-> Show TableOptions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TableOptions] -> ShowS
$cshowList :: [TableOptions] -> ShowS
show :: TableOptions -> String
$cshow :: TableOptions -> String
showsPrec :: Int -> TableOptions -> ShowS
$cshowsPrec :: Int -> TableOptions -> ShowS
Show

defTableOptions :: TableOptions
defTableOptions :: TableOptions
defTableOptions = TableOptions
  { $sel:tableFlags:TableOptions :: ImGuiTableFlags
tableFlags      = ImGuiTableFlags
ImGuiTableFlags_None
  , $sel:tableOuterSize:TableOptions :: ImVec2
tableOuterSize  = Float -> Float -> ImVec2
ImVec2 Float
0  Float
0
  , $sel:tableInnerWidth:TableOptions :: Float
tableInnerWidth = Float
0
  }
-- | Wraps @ImGui::BeginTable()@.
beginTable :: MonadIO m => TableOptions -> Text -> Int -> m Bool
beginTable :: forall (m :: * -> *).
MonadIO m =>
TableOptions -> Text -> Int -> m Bool
beginTable TableOptions{Float
ImGuiTableFlags
ImVec2
tableInnerWidth :: Float
tableOuterSize :: ImVec2
tableFlags :: ImGuiTableFlags
$sel:tableInnerWidth:TableOptions :: TableOptions -> Float
$sel:tableOuterSize:TableOptions :: TableOptions -> ImVec2
$sel:tableFlags:TableOptions :: TableOptions -> ImGuiTableFlags
..} Text
label Int
columns = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
label \CString
labelPtr ->
    ImVec2 -> (Ptr ImVec2 -> IO Bool) -> IO Bool
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with ImVec2
tableOuterSize \Ptr ImVec2
outerSizePtr ->
      CString
-> CInt -> ImGuiTableFlags -> Ptr ImVec2 -> CFloat -> IO Bool
forall (m :: * -> *).
MonadIO m =>
CString
-> CInt -> ImGuiTableFlags -> Ptr ImVec2 -> CFloat -> m Bool
Raw.beginTable CString
labelPtr (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
columns) ImGuiTableFlags
tableFlags Ptr ImVec2
outerSizePtr (Float -> CFloat
CFloat Float
tableInnerWidth)

-- | Create a table.
--
-- The action will get 'False' if the entry is not visible.
--
-- ==== __Example usage:__
--
-- > withTableOpen defTableOptions "MyTable" do
-- >   tableSetupColumn "Hello"
-- >   tableSetupColumn "World"
-- >   tableHeadersRow
-- >
-- >   for_ [("a","1"),("b","2")] \(a,b) -> do
-- >     tableNextRow
-- >     tableNextColumn (text a)
-- >     tableNextColumn (text b)
--
-- Displays:
--
-- @
-- | Hello | World |
-- +-------+-------+
-- | a     | 1     |
-- | b     | 2     |
-- @
--
withTable :: MonadUnliftIO m => TableOptions -> Text -> Int -> (Bool -> m a) -> m a
withTable :: forall (m :: * -> *) a.
MonadUnliftIO m =>
TableOptions -> Text -> Int -> (Bool -> m a) -> m a
withTable TableOptions
options Text
label Int
columns =
  m Bool -> (Bool -> m ()) -> (Bool -> m a) -> m a
forall (m :: * -> *) a b c.
MonadUnliftIO m =>
m a -> (a -> m b) -> (a -> m c) -> m c
bracket (TableOptions -> Text -> Int -> m Bool
forall (m :: * -> *).
MonadIO m =>
TableOptions -> Text -> Int -> m Bool
beginTable TableOptions
options Text
label Int
columns) (Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
`when` m ()
forall (m :: * -> *). MonadIO m => m ()
Raw.endTable)

withTableOpen :: MonadUnliftIO m => TableOptions -> Text -> Int -> m () -> m ()
withTableOpen :: forall (m :: * -> *).
MonadUnliftIO m =>
TableOptions -> Text -> Int -> m () -> m ()
withTableOpen TableOptions
options Text
label Int
columns m ()
action =
  TableOptions -> Text -> Int -> (Bool -> m ()) -> m ()
forall (m :: * -> *) a.
MonadUnliftIO m =>
TableOptions -> Text -> Int -> (Bool -> m a) -> m a
withTable TableOptions
options Text
label Int
columns (Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
`when` m ()
action)

-- | Wraps @ImGui::TableNextRow()@ with 'defTableRowOptions'.
--   append into the first cell of a new row.
tableNextRow :: MonadIO m => m ()
tableNextRow :: forall (m :: * -> *). MonadIO m => m ()
tableNextRow = TableRowOptions -> m ()
forall (m :: * -> *). MonadIO m => TableRowOptions -> m ()
tableNextRowWith TableRowOptions
defTableRowOptions

data TableRowOptions = TableRowOptions
  { TableRowOptions -> ImGuiTableRowFlags
tableRowFlags     :: ImGuiTableRowFlags
  , TableRowOptions -> Float
tableRowMinHeight :: Float
  } deriving Int -> TableRowOptions -> ShowS
[TableRowOptions] -> ShowS
TableRowOptions -> String
(Int -> TableRowOptions -> ShowS)
-> (TableRowOptions -> String)
-> ([TableRowOptions] -> ShowS)
-> Show TableRowOptions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TableRowOptions] -> ShowS
$cshowList :: [TableRowOptions] -> ShowS
show :: TableRowOptions -> String
$cshow :: TableRowOptions -> String
showsPrec :: Int -> TableRowOptions -> ShowS
$cshowsPrec :: Int -> TableRowOptions -> ShowS
Show

defTableRowOptions :: TableRowOptions
defTableRowOptions :: TableRowOptions
defTableRowOptions = TableRowOptions
  { $sel:tableRowFlags:TableRowOptions :: ImGuiTableRowFlags
tableRowFlags     = ImGuiTableRowFlags
ImGuiTableRowFlags_None
  , $sel:tableRowMinHeight:TableRowOptions :: Float
tableRowMinHeight = Float
0
  }

-- | Wraps @ImGui::TableNextRow()@ with explicit options.
tableNextRowWith :: MonadIO m => TableRowOptions -> m ()
tableNextRowWith :: forall (m :: * -> *). MonadIO m => TableRowOptions -> m ()
tableNextRowWith TableRowOptions{Float
ImGuiTableRowFlags
tableRowMinHeight :: Float
tableRowFlags :: ImGuiTableRowFlags
$sel:tableRowMinHeight:TableRowOptions :: TableRowOptions -> Float
$sel:tableRowFlags:TableRowOptions :: TableRowOptions -> ImGuiTableRowFlags
..} = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  ImGuiTableRowFlags -> CFloat -> IO ()
forall (m :: * -> *).
MonadIO m =>
ImGuiTableRowFlags -> CFloat -> m ()
Raw.tableNextRow ImGuiTableRowFlags
tableRowFlags (Float -> CFloat
CFloat Float
tableRowMinHeight)

tableNextColumn :: MonadIO m => m () -> m ()
tableNextColumn :: forall (m :: * -> *). MonadIO m => m () -> m ()
tableNextColumn m ()
action = m Bool
forall (m :: * -> *). MonadIO m => m Bool
Raw.tableNextColumn m Bool -> (Bool -> m ()) -> m ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
`when` m ()
action)

-- | Wraps @ImGui::TableSetColumnIndex()@.
--   append into the specified column. Return true when column is visible.
tableSetColumnIndex :: MonadIO m => Int -> m Bool
tableSetColumnIndex :: forall (m :: * -> *). MonadIO m => Int -> m Bool
tableSetColumnIndex Int
column = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  CInt -> IO Bool
forall (m :: * -> *). MonadIO m => CInt -> m Bool
Raw.tableSetColumnIndex (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
column)

data TableColumnOptions = TableColumnOptions
  { TableColumnOptions -> ImGuiTableColumnFlags
tableColumnFlags             :: ImGuiTableColumnFlags
  , TableColumnOptions -> Float
tableColumnInitWidthOrWeight :: Float
  , TableColumnOptions -> ImGuiID
tableColumnUserId            :: ImGuiID
  } deriving Int -> TableColumnOptions -> ShowS
[TableColumnOptions] -> ShowS
TableColumnOptions -> String
(Int -> TableColumnOptions -> ShowS)
-> (TableColumnOptions -> String)
-> ([TableColumnOptions] -> ShowS)
-> Show TableColumnOptions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TableColumnOptions] -> ShowS
$cshowList :: [TableColumnOptions] -> ShowS
show :: TableColumnOptions -> String
$cshow :: TableColumnOptions -> String
showsPrec :: Int -> TableColumnOptions -> ShowS
$cshowsPrec :: Int -> TableColumnOptions -> ShowS
Show

defTableColumnOptions :: TableColumnOptions
defTableColumnOptions :: TableColumnOptions
defTableColumnOptions = TableColumnOptions
  { $sel:tableColumnFlags:TableColumnOptions :: ImGuiTableColumnFlags
tableColumnFlags             = ImGuiTableColumnFlags
ImGuiTableColumnFlags_None
  , $sel:tableColumnInitWidthOrWeight:TableColumnOptions :: Float
tableColumnInitWidthOrWeight = Float
0
  , $sel:tableColumnUserId:TableColumnOptions :: ImGuiID
tableColumnUserId            = ImGuiID
0
  }

-- | Wraps @ImGui::TableSetupColumn()@ using 'defTableColumnOptions'.
tableSetupColumn :: MonadIO m => Text -> m ()
tableSetupColumn :: forall (m :: * -> *). MonadIO m => Text -> m ()
tableSetupColumn = TableColumnOptions -> Text -> m ()
forall (m :: * -> *).
MonadIO m =>
TableColumnOptions -> Text -> m ()
tableSetupColumnWith TableColumnOptions
defTableColumnOptions

-- | Wraps @ImGui::TableSetupColumn() with explicit options@.
tableSetupColumnWith :: MonadIO m => TableColumnOptions -> Text -> m ()
tableSetupColumnWith :: forall (m :: * -> *).
MonadIO m =>
TableColumnOptions -> Text -> m ()
tableSetupColumnWith TableColumnOptions{Float
ImGuiID
ImGuiTableColumnFlags
tableColumnUserId :: ImGuiID
tableColumnInitWidthOrWeight :: Float
tableColumnFlags :: ImGuiTableColumnFlags
$sel:tableColumnUserId:TableColumnOptions :: TableColumnOptions -> ImGuiID
$sel:tableColumnInitWidthOrWeight:TableColumnOptions :: TableColumnOptions -> Float
$sel:tableColumnFlags:TableColumnOptions :: TableColumnOptions -> ImGuiTableColumnFlags
..} Text
label = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  Text -> (CString -> IO ()) -> IO ()
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
label \CString
labelPtr ->
    CString -> ImGuiTableColumnFlags -> CFloat -> ImGuiID -> IO ()
forall (m :: * -> *).
MonadIO m =>
CString -> ImGuiTableColumnFlags -> CFloat -> ImGuiID -> m ()
Raw.tableSetupColumn CString
labelPtr ImGuiTableColumnFlags
tableColumnFlags (Float -> CFloat
CFloat Float
tableColumnInitWidthOrWeight) ImGuiID
tableColumnUserId

-- | Wraps @ImGui::TableSetupScrollFreeze()@.
--   lock columns/rows so they stay visible when scrolled.
tableSetupScrollFreeze :: MonadIO m => Int -> Int -> m ()
tableSetupScrollFreeze :: forall (m :: * -> *). MonadIO m => Int -> Int -> m ()
tableSetupScrollFreeze Int
cols Int
rows = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  CInt -> CInt -> IO ()
forall (m :: * -> *). MonadIO m => CInt -> CInt -> m ()
Raw.tableSetupScrollFreeze (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
cols) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
rows)

data TableSortingSpecs = TableSortingSpecs
  { TableSortingSpecs -> Int
tableSortingColumn  :: Int -- ^ Index of the column, starting at 0
  , TableSortingSpecs -> Bool
tableSortingReverse :: Bool
  , TableSortingSpecs -> ImGuiID
tableSortingUserId  :: ImGuiID -- ^ User id of the column (if specified by a 'tableSetupColumn' call).
  } deriving (TableSortingSpecs -> TableSortingSpecs -> Bool
(TableSortingSpecs -> TableSortingSpecs -> Bool)
-> (TableSortingSpecs -> TableSortingSpecs -> Bool)
-> Eq TableSortingSpecs
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TableSortingSpecs -> TableSortingSpecs -> Bool
$c/= :: TableSortingSpecs -> TableSortingSpecs -> Bool
== :: TableSortingSpecs -> TableSortingSpecs -> Bool
$c== :: TableSortingSpecs -> TableSortingSpecs -> Bool
Eq, Eq TableSortingSpecs
Eq TableSortingSpecs
-> (TableSortingSpecs -> TableSortingSpecs -> Ordering)
-> (TableSortingSpecs -> TableSortingSpecs -> Bool)
-> (TableSortingSpecs -> TableSortingSpecs -> Bool)
-> (TableSortingSpecs -> TableSortingSpecs -> Bool)
-> (TableSortingSpecs -> TableSortingSpecs -> Bool)
-> (TableSortingSpecs -> TableSortingSpecs -> TableSortingSpecs)
-> (TableSortingSpecs -> TableSortingSpecs -> TableSortingSpecs)
-> Ord TableSortingSpecs
TableSortingSpecs -> TableSortingSpecs -> Bool
TableSortingSpecs -> TableSortingSpecs -> Ordering
TableSortingSpecs -> TableSortingSpecs -> TableSortingSpecs
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: TableSortingSpecs -> TableSortingSpecs -> TableSortingSpecs
$cmin :: TableSortingSpecs -> TableSortingSpecs -> TableSortingSpecs
max :: TableSortingSpecs -> TableSortingSpecs -> TableSortingSpecs
$cmax :: TableSortingSpecs -> TableSortingSpecs -> TableSortingSpecs
>= :: TableSortingSpecs -> TableSortingSpecs -> Bool
$c>= :: TableSortingSpecs -> TableSortingSpecs -> Bool
> :: TableSortingSpecs -> TableSortingSpecs -> Bool
$c> :: TableSortingSpecs -> TableSortingSpecs -> Bool
<= :: TableSortingSpecs -> TableSortingSpecs -> Bool
$c<= :: TableSortingSpecs -> TableSortingSpecs -> Bool
< :: TableSortingSpecs -> TableSortingSpecs -> Bool
$c< :: TableSortingSpecs -> TableSortingSpecs -> Bool
compare :: TableSortingSpecs -> TableSortingSpecs -> Ordering
$ccompare :: TableSortingSpecs -> TableSortingSpecs -> Ordering
Ord, Int -> TableSortingSpecs -> ShowS
[TableSortingSpecs] -> ShowS
TableSortingSpecs -> String
(Int -> TableSortingSpecs -> ShowS)
-> (TableSortingSpecs -> String)
-> ([TableSortingSpecs] -> ShowS)
-> Show TableSortingSpecs
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TableSortingSpecs] -> ShowS
$cshowList :: [TableSortingSpecs] -> ShowS
show :: TableSortingSpecs -> String
$cshow :: TableSortingSpecs -> String
showsPrec :: Int -> TableSortingSpecs -> ShowS
$cshowsPrec :: Int -> TableSortingSpecs -> ShowS
Show)

convertTableSortingSpecs :: ImGuiTableColumnSortSpecs -> TableSortingSpecs
convertTableSortingSpecs :: ImGuiTableColumnSortSpecs -> TableSortingSpecs
convertTableSortingSpecs ImGuiTableColumnSortSpecs{ImS16
ImGuiID
ImGuiSortDirection
$sel:sortDirection:ImGuiTableColumnSortSpecs :: ImGuiTableColumnSortSpecs -> ImGuiSortDirection
$sel:sortOrder:ImGuiTableColumnSortSpecs :: ImGuiTableColumnSortSpecs -> ImS16
$sel:columnIndex:ImGuiTableColumnSortSpecs :: ImGuiTableColumnSortSpecs -> ImS16
$sel:columnUserID:ImGuiTableColumnSortSpecs :: ImGuiTableColumnSortSpecs -> ImGuiID
sortDirection :: ImGuiSortDirection
sortOrder :: ImS16
columnIndex :: ImS16
columnUserID :: ImGuiID
..} =
  TableSortingSpecs
    { $sel:tableSortingColumn:TableSortingSpecs :: Int
tableSortingColumn  = ImS16 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral ImS16
columnIndex
    , $sel:tableSortingReverse:TableSortingSpecs :: Bool
tableSortingReverse = ImGuiSortDirection
sortDirection ImGuiSortDirection -> ImGuiSortDirection -> Bool
forall a. Eq a => a -> a -> Bool
== ImGuiSortDirection
ImGuiSortDirection_Descending
    , $sel:tableSortingUserId:TableSortingSpecs :: ImGuiID
tableSortingUserId  = ImGuiID
columnUserID
    }

-- | High-Level sorting. Returns of the underlying data should be sorted
--   and to what specification. Number of Specifications is mostly 0 or 1, but
--   can be more if 'ImGuiTableFlags_SortMulti' is enabled on the table.
--
--   The Bool only fires true for one frame on each sorting event and resets
--   automatically.
--
--   Must be called AFTER all columns are set up with 'tableSetupColumn'
--
--   Hint: Don't forget to set 'ImGuiTableFlags_Sortable' to enable sorting
--   on tables.
--
-- ==== __Example usage:__
--
-- > sortedData <- newIORef [("a","1"), ("b","2")]
-- >
-- > let sortable = defTableOptions { tableFlags = ImGuiTableFlags_Sortable }
-- > withTableOpen sortable "MyTable" 2 $ do
-- >   tableSetupColumn "Hello"
-- >   tableSetupColumn "World"
-- >
-- >   withSortableTable \isDirty sortSpecs -> do
-- >     when isDirty $
-- >       -- XXX: do your sorting & cache it. Dont sort every frame.
-- >       modifyIORef' sortedData . sortBy $
-- >         foldMap columnSorter sortSpecs
-- >
-- >     tableHeadersRow
-- >     for_ sortedData \(a, b) -> do
-- >       tableNextRow
-- >       tableNextColumn $ text a
-- >       tableNextColumn $ text b
withSortableTable :: MonadIO m => (Bool -> [TableSortingSpecs] -> m ()) -> m ()
withSortableTable :: forall (m :: * -> *).
MonadIO m =>
(Bool -> [TableSortingSpecs] -> m ()) -> m ()
withSortableTable Bool -> [TableSortingSpecs] -> m ()
action = do
  IO (Maybe (Ptr ImGuiTableSortSpecs))
-> m (Maybe (Ptr ImGuiTableSortSpecs))
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO (Maybe (Ptr ImGuiTableSortSpecs))
forall (m :: * -> *).
MonadIO m =>
m (Maybe (Ptr ImGuiTableSortSpecs))
Raw.tableGetSortSpecs m (Maybe (Ptr ImGuiTableSortSpecs))
-> (Maybe (Ptr ImGuiTableSortSpecs) -> m ()) -> m ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
    Maybe (Ptr ImGuiTableSortSpecs)
Nothing ->
      -- XXX: The table is not sortable
      () -> m ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()

    Just Ptr ImGuiTableSortSpecs
specsPtr -> do
      ImGuiTableSortSpecs{Ptr ImGuiTableColumnSortSpecs
CInt
CBool
$sel:specsDirty:ImGuiTableSortSpecs :: ImGuiTableSortSpecs -> CBool
$sel:specsCount:ImGuiTableSortSpecs :: ImGuiTableSortSpecs -> CInt
$sel:specs:ImGuiTableSortSpecs :: ImGuiTableSortSpecs -> Ptr ImGuiTableColumnSortSpecs
specsDirty :: CBool
specsCount :: CInt
specs :: Ptr ImGuiTableColumnSortSpecs
..} <- IO ImGuiTableSortSpecs -> m ImGuiTableSortSpecs
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ImGuiTableSortSpecs -> m ImGuiTableSortSpecs)
-> IO ImGuiTableSortSpecs -> m ImGuiTableSortSpecs
forall a b. (a -> b) -> a -> b
$ Ptr ImGuiTableSortSpecs -> IO ImGuiTableSortSpecs
forall a. Storable a => Ptr a -> IO a
peek Ptr ImGuiTableSortSpecs
specsPtr
      let isDirty :: Bool
isDirty = CBool
0 CBool -> CBool -> Bool
forall a. Eq a => a -> a -> Bool
/= CBool
specsDirty
      [ImGuiTableColumnSortSpecs]
columns <- IO [ImGuiTableColumnSortSpecs] -> m [ImGuiTableColumnSortSpecs]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [ImGuiTableColumnSortSpecs] -> m [ImGuiTableColumnSortSpecs])
-> IO [ImGuiTableColumnSortSpecs] -> m [ImGuiTableColumnSortSpecs]
forall a b. (a -> b) -> a -> b
$ Int
-> Ptr ImGuiTableColumnSortSpecs -> IO [ImGuiTableColumnSortSpecs]
forall a. Storable a => Int -> Ptr a -> IO [a]
peekArray (CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
specsCount) Ptr ImGuiTableColumnSortSpecs
specs

      Bool -> [TableSortingSpecs] -> m ()
action Bool
isDirty ((ImGuiTableColumnSortSpecs -> TableSortingSpecs)
-> [ImGuiTableColumnSortSpecs] -> [TableSortingSpecs]
forall a b. (a -> b) -> [a] -> [b]
map ImGuiTableColumnSortSpecs -> TableSortingSpecs
convertTableSortingSpecs [ImGuiTableColumnSortSpecs]
columns)
      Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
isDirty (m () -> m ()) -> m () -> m ()
forall a b. (a -> b) -> a -> b
$
        Ptr ImGuiTableSortSpecs -> m ()
forall (m :: * -> *). MonadIO m => Ptr ImGuiTableSortSpecs -> m ()
Raw.tableClearSortSpecsDirty Ptr ImGuiTableSortSpecs
specsPtr

-- | Wraps @ImGui::TableGetColumnCount()@.
--   return number of columns (value passed to BeginTable)
tableGetColumnCount :: MonadIO m => m Int
tableGetColumnCount :: forall (m :: * -> *). MonadIO m => m Int
tableGetColumnCount =
  CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CInt -> Int) -> m CInt -> m Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m CInt
forall (m :: * -> *). MonadIO m => m CInt
Raw.tableGetColumnCount

-- | Wraps @ImGui::TableGetColumnIndex()@.
--   return current column index.
tableGetColumnIndex :: MonadIO m => m Int
tableGetColumnIndex :: forall (m :: * -> *). MonadIO m => m Int
tableGetColumnIndex =
  CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CInt -> Int) -> m CInt -> m Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m CInt
forall (m :: * -> *). MonadIO m => m CInt
Raw.tableGetColumnIndex

-- | Wraps @ImGui::TableGetRowIndex()@.
--   return current row index
tableGetRowIndex :: MonadIO m => m Int
tableGetRowIndex :: forall (m :: * -> *). MonadIO m => m Int
tableGetRowIndex =
  CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CInt -> Int) -> m CInt -> m Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m CInt
forall (m :: * -> *). MonadIO m => m CInt
Raw.tableGetRowIndex

-- | Wraps @ImGui::TableGetColumnName
--   returns "" if column didn't have a name declared by TableSetupColumn
--   'Nothing' returns the current column name
tableGetColumnName :: MonadIO m => Maybe Int -> m Text
tableGetColumnName :: forall (m :: * -> *). MonadIO m => Maybe Int -> m Text
tableGetColumnName Maybe Int
c = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  Maybe CInt -> IO CString
forall (m :: * -> *). MonadIO m => Maybe CInt -> m CString
Raw.tableGetColumnName (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> Maybe Int -> Maybe CInt
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Int
c) IO CString -> (CString -> IO Text) -> IO Text
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= CString -> IO Text
Text.peekCString

-- | Wraps @ImGui::TableGetRowIndex()@.
--    return column flags so you can query their Enabled/Visible/Sorted/Hovered
--    status flags.
--   'Nothing' returns the current column flags
tableGetColumnFlags :: MonadIO m => Maybe Int -> m ImGuiTableColumnFlags
tableGetColumnFlags :: forall (m :: * -> *).
MonadIO m =>
Maybe Int -> m ImGuiTableColumnFlags
tableGetColumnFlags =
  Maybe CInt -> m ImGuiTableColumnFlags
forall (m :: * -> *).
MonadIO m =>
Maybe CInt -> m ImGuiTableColumnFlags
Raw.tableGetColumnFlags (Maybe CInt -> m ImGuiTableColumnFlags)
-> (Maybe Int -> Maybe CInt)
-> Maybe Int
-> m ImGuiTableColumnFlags
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> CInt) -> Maybe Int -> Maybe CInt
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral

-- | Wraps @ImGui::TableSetColumnEnabled()@.
--   change user accessible enabled/disabled state of a column. Set to false to
--   hide the column. User can use the context menu to change this themselves
--   (right-click in headers, or right-click in columns body with
--   'ImGuiTableFlags_ContextMenuInBody')
tableSetColumnEnabled :: MonadIO m => Int -> Bool -> m ()
tableSetColumnEnabled :: forall (m :: * -> *). MonadIO m => Int -> Bool -> m ()
tableSetColumnEnabled Int
column_n Bool
v =
  CInt -> CBool -> m ()
forall (m :: * -> *). MonadIO m => CInt -> CBool -> m ()
Raw.tableSetColumnEnabled (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
column_n) (CBool -> CBool -> Bool -> CBool
forall a. a -> a -> Bool -> a
bool CBool
0 CBool
1 Bool
v)

-- | Wraps @ImGui::TableSetBgColor()@.
--   change the color of a cell, row, or column.
--   See 'ImGuiTableBgTarget' flags for details.
--   'Nothing' sets the current row/column color
tableSetBgColor :: MonadIO m => ImGuiTableBgTarget -> ImU32 -> Maybe Int -> m ()
tableSetBgColor :: forall (m :: * -> *).
MonadIO m =>
ImGuiTableBgTarget -> ImGuiID -> Maybe Int -> m ()
tableSetBgColor ImGuiTableBgTarget
target ImGuiID
color Maybe Int
column_n =
 ImGuiTableBgTarget -> ImGuiID -> Maybe CInt -> m ()
forall (m :: * -> *).
MonadIO m =>
ImGuiTableBgTarget -> ImGuiID -> Maybe CInt -> m ()
Raw.tableSetBgColor ImGuiTableBgTarget
target ImGuiID
color (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> Maybe Int -> Maybe CInt
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Int
column_n)

-- | Wraps @ImGui::TreeNode()@.
treeNode :: MonadIO m => Text -> m Bool
treeNode :: forall (m :: * -> *). MonadIO m => Text -> m Bool
treeNode Text
label = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
label CString -> IO Bool
forall (m :: * -> *). MonadIO m => CString -> m Bool
Raw.treeNode


-- | Wraps @ImGui::TreePush()@.
treePush :: MonadIO m => Text -> m ()
treePush :: forall (m :: * -> *). MonadIO m => Text -> m ()
treePush Text
label = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  Text -> (CString -> IO ()) -> IO ()
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
label CString -> IO ()
forall (m :: * -> *). MonadIO m => CString -> m ()
Raw.treePush


-- | Wraps @ImGui::Selectable()@ with default options.
selectable :: MonadIO m => Text -> m Bool
selectable :: forall (m :: * -> *). MonadIO m => Text -> m Bool
selectable = SelectableOptions -> Text -> m Bool
forall (m :: * -> *).
MonadIO m =>
SelectableOptions -> Text -> m Bool
selectableWith SelectableOptions
defSelectableOptions

data SelectableOptions = SelectableOptions
  { SelectableOptions -> Bool
selected :: Bool
  , SelectableOptions -> ImGuiSelectableFlags
flags    :: ImGuiSelectableFlags
  , SelectableOptions -> ImVec2
size     :: ImVec2
  } deriving Int -> SelectableOptions -> ShowS
[SelectableOptions] -> ShowS
SelectableOptions -> String
(Int -> SelectableOptions -> ShowS)
-> (SelectableOptions -> String)
-> ([SelectableOptions] -> ShowS)
-> Show SelectableOptions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SelectableOptions] -> ShowS
$cshowList :: [SelectableOptions] -> ShowS
show :: SelectableOptions -> String
$cshow :: SelectableOptions -> String
showsPrec :: Int -> SelectableOptions -> ShowS
$cshowsPrec :: Int -> SelectableOptions -> ShowS
Show

defSelectableOptions :: SelectableOptions
defSelectableOptions :: SelectableOptions
defSelectableOptions = SelectableOptions
  { $sel:selected:SelectableOptions :: Bool
selected = Bool
False
  , $sel:flags:SelectableOptions :: ImGuiSelectableFlags
flags    = ImGuiSelectableFlags
ImGuiSelectableFlags_None
  , $sel:size:SelectableOptions :: ImVec2
size     = Float -> Float -> ImVec2
ImVec2 Float
0 Float
0
  }

-- | Wraps @ImGui::Selectable()@ with explicit options.
selectableWith :: MonadIO m => SelectableOptions -> Text -> m Bool
selectableWith :: forall (m :: * -> *).
MonadIO m =>
SelectableOptions -> Text -> m Bool
selectableWith (SelectableOptions Bool
selected ImGuiSelectableFlags
flags ImVec2
size) Text
label = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  ImVec2 -> (Ptr ImVec2 -> IO Bool) -> IO Bool
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with ImVec2
size \Ptr ImVec2
sizePtr ->
    Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
label \CString
labelPtr ->
      CString -> CBool -> ImGuiSelectableFlags -> Ptr ImVec2 -> IO Bool
forall (m :: * -> *).
MonadIO m =>
CString -> CBool -> ImGuiSelectableFlags -> Ptr ImVec2 -> m Bool
Raw.selectable CString
labelPtr (CBool -> CBool -> Bool -> CBool
forall a. a -> a -> Bool -> a
bool CBool
0 CBool
1 Bool
selected) ImGuiSelectableFlags
flags Ptr ImVec2
sizePtr


listBox :: (MonadIO m, HasGetter ref Int, HasSetter ref Int) => Text -> ref -> [Text] -> m Bool
listBox :: forall (m :: * -> *) ref.
(MonadIO m, HasGetter ref Int, HasSetter ref Int) =>
Text -> ref -> [Text] -> m Bool
listBox Text
label ref
selectedIndex [Text]
items = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ Managed Bool -> (Bool -> IO Bool) -> IO Bool
forall a r. Managed a -> (a -> IO r) -> IO r
Managed.with Managed Bool
m Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return
  where
    m :: Managed Bool
m = do
      Int
i <- ref -> Managed Int
forall t a (m :: * -> *). (HasGetter t a, MonadIO m) => t -> m a
get ref
selectedIndex

      [CString]
cStrings <- (Text -> Managed CString) -> [Text] -> Managed [CString]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (\Text
str -> (forall r. (CString -> IO r) -> IO r) -> Managed CString
forall (m :: * -> *) a.
MonadManaged m =>
(forall r. (a -> IO r) -> IO r) -> m a
Managed.managed (Text -> (CString -> IO r) -> IO r
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
str)) [Text]
items
      CString
labelPtr <- (forall r. (CString -> IO r) -> IO r) -> Managed CString
forall (m :: * -> *) a.
MonadManaged m =>
(forall r. (a -> IO r) -> IO r) -> m a
Managed.managed ((forall r. (CString -> IO r) -> IO r) -> Managed CString)
-> (forall r. (CString -> IO r) -> IO r) -> Managed CString
forall a b. (a -> b) -> a -> b
$ Text -> (CString -> IO r) -> IO r
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
label
      Ptr CInt
iPtr     <- (forall r. (Ptr CInt -> IO r) -> IO r) -> Managed (Ptr CInt)
forall (m :: * -> *) a.
MonadManaged m =>
(forall r. (a -> IO r) -> IO r) -> m a
Managed.managed ((forall r. (Ptr CInt -> IO r) -> IO r) -> Managed (Ptr CInt))
-> (forall r. (Ptr CInt -> IO r) -> IO r) -> Managed (Ptr CInt)
forall a b. (a -> b) -> a -> b
$ CInt -> (Ptr CInt -> IO r) -> IO r
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
i)

      IO Bool -> Managed Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> Managed Bool) -> IO Bool -> Managed Bool
forall a b. (a -> b) -> a -> b
$ [CString] -> (Int -> Ptr CString -> IO Bool) -> IO Bool
forall a b. Storable a => [a] -> (Int -> Ptr a -> IO b) -> IO b
withArrayLen [CString]
cStrings \Int
len Ptr CString
itemsPtr -> do
        Bool
changed <- CString -> Ptr CInt -> Ptr CString -> CInt -> IO Bool
forall (m :: * -> *).
MonadIO m =>
CString -> Ptr CInt -> Ptr CString -> CInt -> m Bool
Raw.listBox CString
labelPtr Ptr CInt
iPtr Ptr CString
itemsPtr (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
len)

        Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
changed do
          CInt
i' <- Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek Ptr CInt
iPtr
          ref
selectedIndex ref -> Int -> IO ()
forall t a (m :: * -> *).
(HasSetter t a, MonadIO m) =>
t -> a -> m ()
$=! CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
i'

        Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
changed


-- | Wraps @ImGui::PlotHistogram()@.
plotHistogram :: MonadIO m => Text -> [CFloat] -> m ()
plotHistogram :: forall (m :: * -> *). MonadIO m => Text -> [CFloat] -> m ()
plotHistogram Text
label [CFloat]
values = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$
  [CFloat] -> (Int -> Ptr CFloat -> IO ()) -> IO ()
forall a b. Storable a => [a] -> (Int -> Ptr a -> IO b) -> IO b
withArrayLen [CFloat]
values \Int
len Ptr CFloat
valuesPtr ->
    Text -> (CString -> IO ()) -> IO ()
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
label \CString
labelPtr ->
      CString -> Ptr CFloat -> CInt -> IO ()
forall (m :: * -> *).
MonadIO m =>
CString -> Ptr CFloat -> CInt -> m ()
Raw.plotHistogram CString
labelPtr Ptr CFloat
valuesPtr (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
len)

-- | Create a menu bar at the top of the screen and append to it.
--
-- The action will get 'False' if the menu is not visible.
withMainMenuBar :: MonadUnliftIO m => (Bool -> m a) -> m a
withMainMenuBar :: forall (m :: * -> *) a. MonadUnliftIO m => (Bool -> m a) -> m a
withMainMenuBar = m Bool -> (Bool -> m ()) -> (Bool -> m a) -> m a
forall (m :: * -> *) a b c.
MonadUnliftIO m =>
m a -> (a -> m b) -> (a -> m c) -> m c
bracket m Bool
forall (m :: * -> *). MonadIO m => m Bool
Raw.beginMainMenuBar (Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
`when` m ()
forall (m :: * -> *). MonadIO m => m ()
Raw.endMainMenuBar)

-- | Create a menu bar at the top of the screen and append to it.
--
-- The action will be skipped if the menu is not visible.
withMainMenuBarOpen :: MonadUnliftIO m => m () -> m ()
withMainMenuBarOpen :: forall (m :: * -> *). MonadUnliftIO m => m () -> m ()
withMainMenuBarOpen m ()
action =
  (Bool -> m ()) -> m ()
forall (m :: * -> *) a. MonadUnliftIO m => (Bool -> m a) -> m a
withMainMenuBar (Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
`when` m ()
action)

-- | Append items to a window with MenuBar flag.
--
-- The action will get 'False' if the menu is not visible.
withMenuBar :: MonadUnliftIO m => (Bool -> m a) -> m a
withMenuBar :: forall (m :: * -> *) a. MonadUnliftIO m => (Bool -> m a) -> m a
withMenuBar = m Bool -> (Bool -> m ()) -> (Bool -> m a) -> m a
forall (m :: * -> *) a b c.
MonadUnliftIO m =>
m a -> (a -> m b) -> (a -> m c) -> m c
bracket m Bool
forall (m :: * -> *). MonadIO m => m Bool
Raw.beginMenuBar (Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
`when` m ()
forall (m :: * -> *). MonadIO m => m ()
Raw.endMenuBar)

-- | Append items to a window with MenuBar flag.
--
-- The action will be skipped if the menu is not visible.
withMenuBarOpen :: MonadUnliftIO m => m () -> m ()
withMenuBarOpen :: forall (m :: * -> *). MonadUnliftIO m => m () -> m ()
withMenuBarOpen m ()
action =
  (Bool -> m ()) -> m ()
forall (m :: * -> *) a. MonadUnliftIO m => (Bool -> m a) -> m a
withMenuBar (Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
`when` m ()
action)

-- | Create a sub-menu entry.
--
-- Wraps @ImGui::BeginMenu()@.
beginMenu :: MonadIO m => Text -> m Bool
beginMenu :: forall (m :: * -> *). MonadIO m => Text -> m Bool
beginMenu Text
label = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
label CString -> IO Bool
forall (m :: * -> *). MonadIO m => CString -> m Bool
Raw.beginMenu

-- | Create a sub-menu entry.
--
-- The action will get 'False' if the entry is not visible.
withMenu :: MonadUnliftIO m => Text -> (Bool -> m a) -> m a
withMenu :: forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (Bool -> m a) -> m a
withMenu Text
label = m Bool -> (Bool -> m ()) -> (Bool -> m a) -> m a
forall (m :: * -> *) a b c.
MonadUnliftIO m =>
m a -> (a -> m b) -> (a -> m c) -> m c
bracket (Text -> m Bool
forall (m :: * -> *). MonadIO m => Text -> m Bool
beginMenu Text
label) (Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
`when` m ()
forall (m :: * -> *). MonadIO m => m ()
Raw.endMenu)

-- | Create a sub-menu entry.
--
-- The action will be skipped if the entry is not visible.
withMenuOpen :: MonadUnliftIO m => Text -> m () -> m ()
withMenuOpen :: forall (m :: * -> *). MonadUnliftIO m => Text -> m () -> m ()
withMenuOpen Text
label m ()
action =
  Text -> (Bool -> m ()) -> m ()
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (Bool -> m a) -> m a
withMenu Text
label (Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
`when` m ()
action)

-- | Return true when activated. Shortcuts are displayed for convenience but not
-- processed by ImGui at the moment
--
-- Wraps @ImGui::MenuItem()@
menuItem :: MonadIO m => Text -> m Bool
menuItem :: forall (m :: * -> *). MonadIO m => Text -> m Bool
menuItem Text
label = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
label CString -> IO Bool
forall (m :: * -> *). MonadIO m => CString -> m Bool
Raw.menuItem


-- | Create a @TabBar@ and start appending to it.
--
-- Wraps @ImGui::BeginTabBar@.
beginTabBar :: MonadIO m => Text -> ImGuiTabBarFlags -> m Bool
beginTabBar :: forall (m :: * -> *).
MonadIO m =>
Text -> ImGuiTabBarFlags -> m Bool
beginTabBar Text
tabBarID ImGuiTabBarFlags
flags = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
tabBarID \CString
ptr ->
    CString -> ImGuiTabBarFlags -> IO Bool
forall (m :: * -> *).
MonadIO m =>
CString -> ImGuiTabBarFlags -> m Bool
Raw.beginTabBar CString
ptr ImGuiTabBarFlags
flags

-- | Create a @TabBar@ and start appending to it.
--
-- The action will get 'False' if the Tab bar is not visible.
withTabBar :: MonadUnliftIO m => Text -> ImGuiTabBarFlags -> (Bool -> m a) -> m a
withTabBar :: forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> ImGuiTabBarFlags -> (Bool -> m a) -> m a
withTabBar Text
tabBarID ImGuiTabBarFlags
flags =
  m Bool -> (Bool -> m ()) -> (Bool -> m a) -> m a
forall (m :: * -> *) a b c.
MonadUnliftIO m =>
m a -> (a -> m b) -> (a -> m c) -> m c
bracket (Text -> ImGuiTabBarFlags -> m Bool
forall (m :: * -> *).
MonadIO m =>
Text -> ImGuiTabBarFlags -> m Bool
beginTabBar Text
tabBarID ImGuiTabBarFlags
flags) (Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
`when` m ()
forall (m :: * -> *). MonadIO m => m ()
Raw.endTabBar)

-- | Create a @TabBar@ and start appending to it.
--
-- The action will be skipped if the Tab bar is not visible.
withTabBarOpen :: MonadUnliftIO m => Text -> ImGuiTabBarFlags -> m () -> m ()
withTabBarOpen :: forall (m :: * -> *).
MonadUnliftIO m =>
Text -> ImGuiTabBarFlags -> m () -> m ()
withTabBarOpen Text
tabBarID ImGuiTabBarFlags
flags m ()
action =
  Text -> ImGuiTabBarFlags -> (Bool -> m ()) -> m ()
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> ImGuiTabBarFlags -> (Bool -> m a) -> m a
withTabBar Text
tabBarID ImGuiTabBarFlags
flags (Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
`when` m ()
action)

-- | Create a new tab. Returns @True@ if the tab is selected.
--
-- Wraps @ImGui::BeginTabItem@.
beginTabItem :: (MonadIO m, HasGetter ref Bool, HasSetter ref Bool) => Text -> ref -> ImGuiTabBarFlags -> m Bool
beginTabItem :: forall (m :: * -> *) ref.
(MonadIO m, HasGetter ref Bool, HasSetter ref Bool) =>
Text -> ref -> ImGuiTabBarFlags -> m Bool
beginTabItem Text
tabName ref
ref ImGuiTabBarFlags
flags = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  Bool
currentValue <- ref -> IO Bool
forall t a (m :: * -> *). (HasGetter t a, MonadIO m) => t -> m a
get ref
ref
  CBool -> (Ptr CBool -> IO Bool) -> IO Bool
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with (CBool -> CBool -> Bool -> CBool
forall a. a -> a -> Bool -> a
bool CBool
0 CBool
1 Bool
currentValue) \Ptr CBool
refPtr -> do
    Bool
open <- Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
tabName \CString
ptrName ->
      CString -> Ptr CBool -> ImGuiTabBarFlags -> IO Bool
forall (m :: * -> *).
MonadIO m =>
CString -> Ptr CBool -> ImGuiTabBarFlags -> m Bool
Raw.beginTabItem CString
ptrName Ptr CBool
refPtr ImGuiTabBarFlags
flags

    Bool
newValue <- (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
<$> Ptr CBool -> IO CBool
forall a. Storable a => Ptr a -> IO a
peek Ptr CBool
refPtr
    Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool
newValue Bool -> Bool -> Bool
forall a. Eq a => a -> a -> Bool
/= Bool
currentValue) do
      ref
ref ref -> Bool -> IO ()
forall t a (m :: * -> *).
(HasSetter t a, MonadIO m) =>
t -> a -> m ()
$=! Bool
newValue

    Bool -> IO Bool
forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
open

-- | Create a new tab.
--
-- The action will get 'True' if the tab is selected.
withTabItem :: (MonadUnliftIO m, HasGetter ref Bool, HasSetter ref Bool) => Text -> ref -> ImGuiTabBarFlags -> (Bool -> m a) -> m a
withTabItem :: forall (m :: * -> *) ref a.
(MonadUnliftIO m, HasGetter ref Bool, HasSetter ref Bool) =>
Text -> ref -> ImGuiTabBarFlags -> (Bool -> m a) -> m a
withTabItem Text
tabName ref
ref ImGuiTabBarFlags
flags =
  m Bool -> (Bool -> m ()) -> (Bool -> m a) -> m a
forall (m :: * -> *) a b c.
MonadUnliftIO m =>
m a -> (a -> m b) -> (a -> m c) -> m c
bracket (Text -> ref -> ImGuiTabBarFlags -> m Bool
forall (m :: * -> *) ref.
(MonadIO m, HasGetter ref Bool, HasSetter ref Bool) =>
Text -> ref -> ImGuiTabBarFlags -> m Bool
beginTabItem Text
tabName ref
ref ImGuiTabBarFlags
flags) (Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
`when` m ()
forall (m :: * -> *). MonadIO m => m ()
Raw.endTabItem)

-- | Create a new tab.
--
-- The action will be skipped unless the tab is selected.
withTabItemOpen :: (MonadUnliftIO m, HasGetter ref Bool, HasSetter ref Bool) => Text -> ref -> ImGuiTabBarFlags -> m () -> m ()
withTabItemOpen :: forall (m :: * -> *) ref.
(MonadUnliftIO m, HasGetter ref Bool, HasSetter ref Bool) =>
Text -> ref -> ImGuiTabBarFlags -> m () -> m ()
withTabItemOpen Text
tabName ref
ref ImGuiTabBarFlags
flags m ()
action =
  Text -> ref -> ImGuiTabBarFlags -> (Bool -> m ()) -> m ()
forall (m :: * -> *) ref a.
(MonadUnliftIO m, HasGetter ref Bool, HasSetter ref Bool) =>
Text -> ref -> ImGuiTabBarFlags -> (Bool -> m a) -> m a
withTabItem Text
tabName ref
ref ImGuiTabBarFlags
flags (Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
`when` m ()
action)

-- | 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 => Text -> ImGuiTabItemFlags -> m Bool
tabItemButton :: forall (m :: * -> *).
MonadIO m =>
Text -> ImGuiTabItemFlags -> m Bool
tabItemButton Text
tabName ImGuiTabItemFlags
flags = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
tabName \CString
namePtr ->
    CString -> ImGuiTabItemFlags -> IO Bool
forall (m :: * -> *).
MonadIO m =>
CString -> ImGuiTabItemFlags -> m Bool
Raw.tabItemButton CString
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 => Text -> m ()
setTabItemClosed :: forall (m :: * -> *). MonadIO m => Text -> m ()
setTabItemClosed Text
tabName = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  Text -> (CString -> IO ()) -> IO ()
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
tabName CString -> IO ()
forall (m :: * -> *). MonadIO m => CString -> m ()
Raw.setTabItemClosed

-- | Create a tooltip.
--
-- Those are windows that follow a mouse and don't take focus away.
-- Can contain any kind of items.
withTooltip ::  MonadUnliftIO m => m a -> m a
withTooltip :: forall (m :: * -> *) a. MonadUnliftIO m => m a -> m a
withTooltip = m () -> m () -> m a -> m a
forall (m :: * -> *) a b c.
MonadUnliftIO m =>
m a -> m b -> m c -> m c
bracket_ m ()
forall (m :: * -> *). MonadIO m => m ()
Raw.beginTooltip m ()
forall (m :: * -> *). MonadIO m => m ()
Raw.endTooltip

-- | Returns 'True' if the popup is open, and you can start outputting to it.
--
-- Wraps @ImGui::BeginPopup()@
beginPopup :: MonadIO m => Text -> m Bool
beginPopup :: forall (m :: * -> *). MonadIO m => Text -> m Bool
beginPopup Text
popupId = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
popupId CString -> IO Bool
forall (m :: * -> *). MonadIO m => CString -> m Bool
Raw.beginPopup

-- | Append intems to a non-modal Popup.
--
-- Non-modal popups can be closed by clicking anywhere outside them,
-- or by pressing ESCAPE.
--
-- Visibility state is held internally instead of being held by the programmer.
--
-- The action will get 'True' if the popup is open.
withPopup :: MonadUnliftIO m => Text -> (Bool -> m a) -> m a
withPopup :: forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (Bool -> m a) -> m a
withPopup Text
popupId = m Bool -> (Bool -> m ()) -> (Bool -> m a) -> m a
forall (m :: * -> *) a b c.
MonadUnliftIO m =>
m a -> (a -> m b) -> (a -> m c) -> m c
bracket (Text -> m Bool
forall (m :: * -> *). MonadIO m => Text -> m Bool
beginPopup Text
popupId) (Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
`when` m ()
forall (m :: * -> *). MonadIO m => m ()
Raw.endPopup)

-- | Append intems to a non-modal Popup.
--
-- Non-modal popups can be closed by clicking anywhere outside them,
-- or by pressing ESCAPE.
--
-- Visibility state is held internally instead of being held by the programmer.
--
-- The action will be called only if the popup is open.
withPopupOpen :: MonadUnliftIO m => Text -> m () -> m ()
withPopupOpen :: forall (m :: * -> *). MonadUnliftIO m => Text -> m () -> m ()
withPopupOpen Text
popupId m ()
action =
  Text -> (Bool -> m ()) -> m ()
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (Bool -> m a) -> m a
withPopup Text
popupId (Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
`when` m ()
action)

-- | Returns 'True' if the modal is open, and you can start outputting to it.
--
-- Wraps @ImGui::BeginPopupModal()@
beginPopupModal :: MonadIO m => Text -> m Bool
beginPopupModal :: forall (m :: * -> *). MonadIO m => Text -> m Bool
beginPopupModal Text
popupId = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
popupId CString -> IO Bool
forall (m :: * -> *). MonadIO m => CString -> m Bool
Raw.beginPopupModal

-- | Append intems to a modal Popup.
--
-- Modal popups can be closed only with 'closeCurrentPopup'.
--
-- Visibility state is held internally instead of being held by the programmer.
--
-- The action will get 'True' if the popup is open.
withPopupModal :: MonadUnliftIO m => Text -> (Bool -> m a) -> m a
withPopupModal :: forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (Bool -> m a) -> m a
withPopupModal Text
popupId = m Bool -> (Bool -> m ()) -> (Bool -> m a) -> m a
forall (m :: * -> *) a b c.
MonadUnliftIO m =>
m a -> (a -> m b) -> (a -> m c) -> m c
bracket (Text -> m Bool
forall (m :: * -> *). MonadIO m => Text -> m Bool
beginPopupModal Text
popupId) (Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
`when` m ()
forall (m :: * -> *). MonadIO m => m ()
Raw.endPopup)

-- | Append intems to a modal Popup.
--
-- Modal popups can be closed only with 'closeCurrentPopup'.
--
-- Visibility state is held internally instead of being held by the programmer.
--
-- The action will be called only if the popup is open.
withPopupModalOpen :: MonadUnliftIO m => Text -> m () -> m ()
withPopupModalOpen :: forall (m :: * -> *). MonadUnliftIO m => Text -> m () -> m ()
withPopupModalOpen Text
popupId m ()
action =
  Text -> (Bool -> m ()) -> m ()
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (Bool -> m a) -> m a
withPopupModal Text
popupId (Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
`when` m ()
action)

beginPopupContextItem :: MonadIO m => Maybe Text -> ImGuiPopupFlags -> m Bool
beginPopupContextItem :: forall (m :: * -> *).
MonadIO m =>
Maybe Text -> ImGuiPopupFlags -> m Bool
beginPopupContextItem Maybe Text
itemId ImGuiPopupFlags
flags = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  Maybe Text -> (CString -> IO Bool) -> IO Bool
forall a. Maybe Text -> (CString -> IO a) -> IO a
Text.withCStringOrNull Maybe Text
itemId \CString
popupIdPtr ->
    CString -> ImGuiPopupFlags -> IO Bool
forall (m :: * -> *).
MonadIO m =>
CString -> ImGuiPopupFlags -> m Bool
Raw.beginPopupContextItem CString
popupIdPtr ImGuiPopupFlags
flags

withPopupContextItem :: MonadUnliftIO m => Maybe Text -> ImGuiPopupFlags -> (Bool -> m a) -> m a
withPopupContextItem :: forall (m :: * -> *) a.
MonadUnliftIO m =>
Maybe Text -> ImGuiPopupFlags -> (Bool -> m a) -> m a
withPopupContextItem Maybe Text
popupId ImGuiPopupFlags
flags = m Bool -> (Bool -> m ()) -> (Bool -> m a) -> m a
forall (m :: * -> *) a b c.
MonadUnliftIO m =>
m a -> (a -> m b) -> (a -> m c) -> m c
bracket (Maybe Text -> ImGuiPopupFlags -> m Bool
forall (m :: * -> *).
MonadIO m =>
Maybe Text -> ImGuiPopupFlags -> m Bool
beginPopupContextItem Maybe Text
popupId ImGuiPopupFlags
flags) (Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
`when` m ()
forall (m :: * -> *). MonadIO m => m ()
Raw.endPopup)

withPopupContextItemOpen :: MonadUnliftIO m => Maybe Text -> ImGuiPopupFlags -> m () -> m ()
withPopupContextItemOpen :: forall (m :: * -> *).
MonadUnliftIO m =>
Maybe Text -> ImGuiPopupFlags -> m () -> m ()
withPopupContextItemOpen Maybe Text
popupId ImGuiPopupFlags
flags m ()
action = Maybe Text -> ImGuiPopupFlags -> (Bool -> m ()) -> m ()
forall (m :: * -> *) a.
MonadUnliftIO m =>
Maybe Text -> ImGuiPopupFlags -> (Bool -> m a) -> m a
withPopupContextItem Maybe Text
popupId ImGuiPopupFlags
flags (Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
`when` m ()
action)

-- | Attach item context popup to right mouse button click on a last item.
itemContextPopup :: MonadUnliftIO m => m () -> m ()
itemContextPopup :: forall (m :: * -> *). MonadUnliftIO m => m () -> m ()
itemContextPopup = Maybe Text -> ImGuiPopupFlags -> m () -> m ()
forall (m :: * -> *).
MonadUnliftIO m =>
Maybe Text -> ImGuiPopupFlags -> m () -> m ()
withPopupContextItemOpen Maybe Text
forall a. Maybe a
Nothing ImGuiPopupFlags
ImGuiPopupFlags_MouseButtonRight

beginPopupContextWindow :: MonadIO m => Maybe Text -> ImGuiPopupFlags -> m Bool
beginPopupContextWindow :: forall (m :: * -> *).
MonadIO m =>
Maybe Text -> ImGuiPopupFlags -> m Bool
beginPopupContextWindow Maybe Text
popupId ImGuiPopupFlags
flags = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  Maybe Text -> (CString -> IO Bool) -> IO Bool
forall a. Maybe Text -> (CString -> IO a) -> IO a
Text.withCStringOrNull Maybe Text
popupId \CString
popupIdPtr ->
    CString -> ImGuiPopupFlags -> IO Bool
forall (m :: * -> *).
MonadIO m =>
CString -> ImGuiPopupFlags -> m Bool
Raw.beginPopupContextWindow CString
popupIdPtr ImGuiPopupFlags
flags

withPopupContextWindow :: MonadUnliftIO m => Maybe Text -> ImGuiPopupFlags -> (Bool -> m a) -> m a
withPopupContextWindow :: forall (m :: * -> *) a.
MonadUnliftIO m =>
Maybe Text -> ImGuiPopupFlags -> (Bool -> m a) -> m a
withPopupContextWindow Maybe Text
popupId ImGuiPopupFlags
flags = m Bool -> (Bool -> m ()) -> (Bool -> m a) -> m a
forall (m :: * -> *) a b c.
MonadUnliftIO m =>
m a -> (a -> m b) -> (a -> m c) -> m c
bracket (Maybe Text -> ImGuiPopupFlags -> m Bool
forall (m :: * -> *).
MonadIO m =>
Maybe Text -> ImGuiPopupFlags -> m Bool
beginPopupContextWindow Maybe Text
popupId ImGuiPopupFlags
flags) (Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
`when` m ()
forall (m :: * -> *). MonadIO m => m ()
Raw.endPopup)

withPopupContextWindowOpen :: MonadUnliftIO m => Maybe Text -> ImGuiPopupFlags -> m () -> m ()
withPopupContextWindowOpen :: forall (m :: * -> *).
MonadUnliftIO m =>
Maybe Text -> ImGuiPopupFlags -> m () -> m ()
withPopupContextWindowOpen Maybe Text
popupId ImGuiPopupFlags
flags m ()
action = Maybe Text -> ImGuiPopupFlags -> (Bool -> m ()) -> m ()
forall (m :: * -> *) a.
MonadUnliftIO m =>
Maybe Text -> ImGuiPopupFlags -> (Bool -> m a) -> m a
withPopupContextWindow Maybe Text
popupId ImGuiPopupFlags
flags (Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
`when` m ()
action)

-- | Attach item context popup to right mouse button click on a current window.
windowContextPopup :: MonadUnliftIO m => m () -> m ()
windowContextPopup :: forall (m :: * -> *). MonadUnliftIO m => m () -> m ()
windowContextPopup = Maybe Text -> ImGuiPopupFlags -> m () -> m ()
forall (m :: * -> *).
MonadUnliftIO m =>
Maybe Text -> ImGuiPopupFlags -> m () -> m ()
withPopupContextWindowOpen Maybe Text
forall a. Maybe a
Nothing ImGuiPopupFlags
ImGuiPopupFlags_MouseButtonRight

beginPopupContextVoid :: MonadIO m => Maybe Text -> ImGuiPopupFlags -> m Bool
beginPopupContextVoid :: forall (m :: * -> *).
MonadIO m =>
Maybe Text -> ImGuiPopupFlags -> m Bool
beginPopupContextVoid Maybe Text
popupId ImGuiPopupFlags
flags = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  Maybe Text -> (CString -> IO Bool) -> IO Bool
forall a. Maybe Text -> (CString -> IO a) -> IO a
Text.withCStringOrNull Maybe Text
popupId \CString
popupIdPtr ->
    CString -> ImGuiPopupFlags -> IO Bool
forall (m :: * -> *).
MonadIO m =>
CString -> ImGuiPopupFlags -> m Bool
Raw.beginPopupContextVoid CString
popupIdPtr ImGuiPopupFlags
flags

withPopupContextVoid :: MonadUnliftIO m => Maybe Text -> ImGuiPopupFlags -> (Bool -> m a) -> m a
withPopupContextVoid :: forall (m :: * -> *) a.
MonadUnliftIO m =>
Maybe Text -> ImGuiPopupFlags -> (Bool -> m a) -> m a
withPopupContextVoid Maybe Text
popupId ImGuiPopupFlags
flags = m Bool -> (Bool -> m ()) -> (Bool -> m a) -> m a
forall (m :: * -> *) a b c.
MonadUnliftIO m =>
m a -> (a -> m b) -> (a -> m c) -> m c
bracket (Maybe Text -> ImGuiPopupFlags -> m Bool
forall (m :: * -> *).
MonadIO m =>
Maybe Text -> ImGuiPopupFlags -> m Bool
beginPopupContextVoid Maybe Text
popupId ImGuiPopupFlags
flags) (Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
`when` m ()
forall (m :: * -> *). MonadIO m => m ()
Raw.endPopup)

withPopupContextVoidOpen :: MonadUnliftIO m => Maybe Text -> ImGuiPopupFlags -> m () -> m ()
withPopupContextVoidOpen :: forall (m :: * -> *).
MonadUnliftIO m =>
Maybe Text -> ImGuiPopupFlags -> m () -> m ()
withPopupContextVoidOpen Maybe Text
popupId ImGuiPopupFlags
flags m ()
action = Maybe Text -> ImGuiPopupFlags -> (Bool -> m ()) -> m ()
forall (m :: * -> *) a.
MonadUnliftIO m =>
Maybe Text -> ImGuiPopupFlags -> (Bool -> m a) -> m a
withPopupContextVoid Maybe Text
popupId ImGuiPopupFlags
flags (Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
`when` m ()
action)

-- | Attach item context popup to right mouse button click outside of any windows.
voidContextPopup :: MonadUnliftIO m => m () -> m ()
voidContextPopup :: forall (m :: * -> *). MonadUnliftIO m => m () -> m ()
voidContextPopup = Maybe Text -> ImGuiPopupFlags -> m () -> m ()
forall (m :: * -> *).
MonadUnliftIO m =>
Maybe Text -> ImGuiPopupFlags -> m () -> m ()
withPopupContextWindowOpen Maybe Text
forall a. Maybe a
Nothing ImGuiPopupFlags
ImGuiPopupFlags_MouseButtonRight


-- | Call to mark popup as open (don't call every frame!).
--
-- Wraps @ImGui::OpenPopup()@
openPopup :: MonadIO m => Text -> m ()
openPopup :: forall (m :: * -> *). MonadIO m => Text -> m ()
openPopup Text
popupId = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  Text -> (CString -> IO ()) -> IO ()
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
popupId CString -> IO ()
forall (m :: * -> *). MonadIO m => CString -> m ()
Raw.openPopup

-- | Opens a defined popup (i.e. defined with 'withPopup') on defined action.
--
-- Example:
--
-- > openPopupOnItemClick "myPopup" ImGuiPopupFlags_MouseButtonRight
--
-- Wraps @ImGui::OpenPopup()@
openPopupOnItemClick :: MonadIO m => Text -> ImGuiPopupFlags -> m ()
openPopupOnItemClick :: forall (m :: * -> *). MonadIO m => Text -> ImGuiPopupFlags -> m ()
openPopupOnItemClick Text
popupId ImGuiPopupFlags
flags = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  Text -> (CString -> IO ()) -> IO ()
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
popupId ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \CString
idPtr ->
    CString -> ImGuiPopupFlags -> IO ()
forall (m :: * -> *).
MonadIO m =>
CString -> ImGuiPopupFlags -> m ()
Raw.openPopupOnItemClick CString
idPtr ImGuiPopupFlags
flags

-- | Check if the popup is open at the current 'beginPopup' level of the popup stack.
isCurrentPopupOpen :: MonadIO m => Text -> m Bool
isCurrentPopupOpen :: forall (m :: * -> *). MonadIO m => Text -> m Bool
isCurrentPopupOpen Text
popupId = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
popupId ((CString -> IO Bool) -> IO Bool)
-> (CString -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \CString
idPtr ->
    CString -> ImGuiPopupFlags -> IO Bool
forall (m :: * -> *).
MonadIO m =>
CString -> ImGuiPopupFlags -> m Bool
Raw.isPopupOpen CString
idPtr ImGuiPopupFlags
ImGuiPopupFlags_None

-- | Check if *any* popup is open at the current 'beginPopup' level of the popup stack.
isAnyPopupOpen :: MonadIO m => Text -> m Bool
isAnyPopupOpen :: forall (m :: * -> *). MonadIO m => Text -> m Bool
isAnyPopupOpen Text
popupId = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
popupId ((CString -> IO Bool) -> IO Bool)
-> (CString -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \CString
idPtr ->
    CString -> ImGuiPopupFlags -> IO Bool
forall (m :: * -> *).
MonadIO m =>
CString -> ImGuiPopupFlags -> m Bool
Raw.isPopupOpen CString
idPtr ImGuiPopupFlags
ImGuiPopupFlags_AnyPopupId

-- | Check if *any* popup is open at any level of the popup stack.
isAnyLevelPopupOpen :: MonadIO m => Text -> m Bool
isAnyLevelPopupOpen :: forall (m :: * -> *). MonadIO m => Text -> m Bool
isAnyLevelPopupOpen Text
popupId = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  Text -> (CString -> IO Bool) -> IO Bool
forall (m :: * -> *) a.
MonadUnliftIO m =>
Text -> (CString -> m a) -> m a
Text.withCString Text
popupId ((CString -> IO Bool) -> IO Bool)
-> (CString -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \CString
idPtr ->
    CString -> ImGuiPopupFlags -> IO Bool
forall (m :: * -> *).
MonadIO m =>
CString -> ImGuiPopupFlags -> m Bool
Raw.isPopupOpen CString
idPtr (ImGuiPopupFlags -> IO Bool) -> ImGuiPopupFlags -> IO Bool
forall a b. (a -> b) -> a -> b
$
      ImGuiPopupFlags
ImGuiPopupFlags_AnyPopupId ImGuiPopupFlags -> ImGuiPopupFlags -> ImGuiPopupFlags
forall a. Bits a => a -> a -> a
.|. ImGuiPopupFlags
ImGuiPopupFlags_AnyPopupLevel


-- | 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, HasGetter ref ImVec2)
  => ref
  -> ImGuiCond
  -> Maybe ref -- XXX: the type should be distinct, but using `setNextWindowPos .. Nothing` is ambiguous resulting in bad UX.
  -> m ()
setNextWindowPos :: forall (m :: * -> *) ref.
(MonadIO m, HasGetter ref ImVec2) =>
ref -> ImGuiCond -> Maybe ref -> m ()
setNextWindowPos ref
posRef ImGuiCond
cond Maybe ref
pivotMaybe = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  ImVec2
pos <- ref -> IO ImVec2
forall t a (m :: * -> *). (HasGetter t a, MonadIO m) => t -> m a
get ref
posRef
  ImVec2 -> (Ptr ImVec2 -> IO ()) -> IO ()
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with ImVec2
pos ((Ptr ImVec2 -> IO ()) -> IO ()) -> (Ptr ImVec2 -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr ImVec2
posPtr ->
    case Maybe ref
pivotMaybe of
      Just ref
pivotRef -> do
        ImVec2
pivot <- ref -> IO ImVec2
forall t a (m :: * -> *). (HasGetter t a, MonadIO m) => t -> m a
get ref
pivotRef
        ImVec2 -> (Ptr ImVec2 -> IO ()) -> IO ()
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with ImVec2
pivot ((Ptr ImVec2 -> IO ()) -> IO ()) -> (Ptr ImVec2 -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr ImVec2
pivotPtr ->
          Ptr ImVec2 -> ImGuiCond -> Maybe (Ptr ImVec2) -> IO ()
forall (m :: * -> *).
MonadIO m =>
Ptr ImVec2 -> ImGuiCond -> Maybe (Ptr ImVec2) -> m ()
Raw.setNextWindowPos Ptr ImVec2
posPtr ImGuiCond
cond (Ptr ImVec2 -> Maybe (Ptr ImVec2)
forall a. a -> Maybe a
Just Ptr ImVec2
pivotPtr)
      Maybe ref
Nothing ->
        Ptr ImVec2 -> ImGuiCond -> Maybe (Ptr ImVec2) -> IO ()
forall (m :: * -> *).
MonadIO m =>
Ptr ImVec2 -> ImGuiCond -> Maybe (Ptr ImVec2) -> m ()
Raw.setNextWindowPos Ptr ImVec2
posPtr ImGuiCond
cond Maybe (Ptr ImVec2)
forall a. Maybe a
Nothing

-- | Set next window size. Call before `begin`
--
-- Wraps @ImGui::SetNextWindowSize()@
setNextWindowSize :: (MonadIO m, HasGetter ref ImVec2) => ref -> ImGuiCond -> m ()
setNextWindowSize :: forall (m :: * -> *) ref.
(MonadIO m, HasGetter ref ImVec2) =>
ref -> ImGuiCond -> m ()
setNextWindowSize ref
sizeRef ImGuiCond
cond = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  ImVec2
size' <- ref -> IO ImVec2
forall t a (m :: * -> *). (HasGetter t a, MonadIO m) => t -> m a
get ref
sizeRef
  ImVec2 -> (Ptr ImVec2 -> IO ()) -> IO ()
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with ImVec2
size' \Ptr ImVec2
sizePtr ->
    Ptr ImVec2 -> ImGuiCond -> IO ()
forall (m :: * -> *). MonadIO m => Ptr ImVec2 -> ImGuiCond -> m ()
Raw.setNextWindowSize Ptr ImVec2
sizePtr ImGuiCond
cond

-- | 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, HasGetter ref ImVec2) => ref -> m ()
setNextWindowContentSize :: forall (m :: * -> *) ref.
(MonadIO m, HasGetter ref ImVec2) =>
ref -> m ()
setNextWindowContentSize ref
sizeRef = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  ImVec2
size' <- ref -> IO ImVec2
forall t a (m :: * -> *). (HasGetter t a, MonadIO m) => t -> m a
get ref
sizeRef
  ImVec2 -> (Ptr ImVec2 -> IO ()) -> IO ()
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with ImVec2
size' Ptr ImVec2 -> IO ()
forall (m :: * -> *). MonadIO m => Ptr ImVec2 -> m ()
Raw.setNextWindowContentSize


-- | 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, HasGetter ref ImVec2) => ref -> ref -> m ()
setNextWindowSizeConstraints :: forall (m :: * -> *) ref.
(MonadIO m, HasGetter ref ImVec2) =>
ref -> ref -> m ()
setNextWindowSizeConstraints ref
sizeMinRef ref
sizeMaxRef = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  ImVec2
sizeMin <- ref -> IO ImVec2
forall t a (m :: * -> *). (HasGetter t a, MonadIO m) => t -> m a
get ref
sizeMinRef
  ImVec2
sizeMax <- ref -> IO ImVec2
forall t a (m :: * -> *). (HasGetter t a, MonadIO m) => t -> m a
get ref
sizeMaxRef
  ImVec2 -> (Ptr ImVec2 -> IO ()) -> IO ()
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with ImVec2
sizeMin \Ptr ImVec2
sizeMinPtr ->
    ImVec2 -> (Ptr ImVec2 -> IO ()) -> IO ()
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with ImVec2
sizeMax \Ptr ImVec2
sizeMaxPtr ->
      Ptr ImVec2 -> Ptr ImVec2 -> IO ()
forall (m :: * -> *). MonadIO m => Ptr ImVec2 -> Ptr ImVec2 -> m ()
Raw.setNextWindowSizeConstraints Ptr ImVec2
sizeMinPtr Ptr ImVec2
sizeMaxPtr


-- | Set next window collapsed state. call before `begin`
--
-- Wraps @ImGui::SetNextWindowCollapsed()@
setNextWindowCollapsed :: (MonadIO m) => Bool -> ImGuiCond -> m ()
setNextWindowCollapsed :: forall (m :: * -> *). MonadIO m => Bool -> ImGuiCond -> m ()
setNextWindowCollapsed Bool
b ImGuiCond
cond = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  CBool -> ImGuiCond -> IO ()
forall (m :: * -> *). MonadIO m => CBool -> ImGuiCond -> m ()
Raw.setNextWindowCollapsed (CBool -> CBool -> Bool -> CBool
forall a. a -> a -> Bool -> a
bool CBool
0 CBool
1 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) => Float -> m ()
setNextWindowBgAlpha :: forall (m :: * -> *). MonadIO m => Float -> m ()
setNextWindowBgAlpha Float
alpha = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  CFloat -> IO ()
forall (m :: * -> *). MonadIO m => CFloat -> m ()
Raw.setNextWindowBgAlpha (Float -> CFloat
CFloat Float
alpha)


-- | 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, HasGetter ref ImVec2) => ref -> m ()
dummy :: forall (m :: * -> *) ref.
(MonadIO m, HasGetter ref ImVec2) =>
ref -> m ()
dummy ref
sizeRef = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  ImVec2
size' <- ref -> IO ImVec2
forall t a (m :: * -> *). (HasGetter t a, MonadIO m) => t -> m a
get ref
sizeRef
  ImVec2 -> (Ptr ImVec2 -> IO ()) -> IO ()
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with ImVec2
size' Ptr ImVec2 -> IO ()
forall (m :: * -> *). MonadIO m => Ptr ImVec2 -> m ()
Raw.dummy

withIndent :: MonadUnliftIO m => Float -> m a -> m a
withIndent :: forall (m :: * -> *) a. MonadUnliftIO m => Float -> m a -> m a
withIndent Float
width =
  m () -> m () -> m a -> m a
forall (m :: * -> *) a b c.
MonadUnliftIO m =>
m a -> m b -> m c -> m c
bracket_ (Float -> m ()
forall (m :: * -> *). MonadIO m => Float -> m ()
indent Float
width) (Float -> m ()
forall (m :: * -> *). MonadIO m => Float -> m ()
unindent Float
width)

-- | Move content position toward the right, by indent_w, or style.IndentSpacing if indent_w <= 0
--
-- Wraps @ImGui::Indent()@
indent :: (MonadIO m) => Float -> m ()
indent :: forall (m :: * -> *). MonadIO m => Float -> m ()
indent Float
indent_w = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  CFloat -> IO ()
forall (m :: * -> *). MonadIO m => CFloat -> m ()
Raw.indent (Float -> CFloat
CFloat 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) => Float -> m ()
unindent :: forall (m :: * -> *). MonadIO m => Float -> m ()
unindent Float
f = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  CFloat -> IO ()
forall (m :: * -> *). MonadIO m => CFloat -> m ()
Raw.unindent (Float -> CFloat
CFloat Float
f)


-- | Affect large frame+labels widgets only.
--
-- Wraps @ImGui::SetNextItemWidth()@
setNextItemWidth :: (MonadIO m) => Float -> m ()
setNextItemWidth :: forall (m :: * -> *). MonadIO m => Float -> m ()
setNextItemWidth Float
itemWidth = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  CFloat -> IO ()
forall (m :: * -> *). MonadIO m => CFloat -> m ()
Raw.setNextItemWidth (Float -> CFloat
CFloat Float
itemWidth)


withItemWidth :: MonadUnliftIO m => Float -> m a -> m a
withItemWidth :: forall (m :: * -> *) a. MonadUnliftIO m => Float -> m a -> m a
withItemWidth Float
width =
  m () -> m () -> m a -> m a
forall (m :: * -> *) a b c.
MonadUnliftIO m =>
m a -> m b -> m c -> m c
bracket_ (Float -> m ()
forall (m :: * -> *). MonadIO m => Float -> m ()
pushItemWidth Float
width) m ()
forall (m :: * -> *). MonadIO m => m ()
Raw.popItemWidth

-- Wraps @ImGui::PushItemWidth()@
pushItemWidth :: (MonadIO m) => Float -> m ()
pushItemWidth :: forall (m :: * -> *). MonadIO m => Float -> m ()
pushItemWidth Float
itemWidth = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  CFloat -> IO ()
forall (m :: * -> *). MonadIO m => CFloat -> m ()
Raw.pushItemWidth (Float -> CFloat
CFloat Float
itemWidth)


-- | Lock horizontal starting position
--
-- Wraps @ImGui::BeginGroup()@ and @ImGui::EndGroup()@
withGroup :: MonadUnliftIO m => m a -> m a
withGroup :: forall (m :: * -> *) a. MonadUnliftIO m => m a -> m a
withGroup = m () -> m () -> m a -> m a
forall (m :: * -> *) a b c.
MonadUnliftIO m =>
m a -> m b -> m c -> m c
bracket_ m ()
forall (m :: * -> *). MonadIO m => m ()
Raw.beginGroup m ()
forall (m :: * -> *). MonadIO m => m ()
Raw.endGroup

-- | Set cursor position in window-local coordinates
--
-- Wraps @ImGui::SetCursorPos()@
setCursorPos :: (MonadIO m, HasGetter ref ImVec2) => ref -> m ()
setCursorPos :: forall (m :: * -> *) ref.
(MonadIO m, HasGetter ref ImVec2) =>
ref -> m ()
setCursorPos ref
posRef = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  ImVec2
pos <- ref -> IO ImVec2
forall t a (m :: * -> *). (HasGetter t a, MonadIO m) => t -> m a
get ref
posRef
  ImVec2 -> (Ptr ImVec2 -> IO ()) -> IO ()
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with ImVec2
pos Ptr ImVec2 -> IO ()
forall (m :: * -> *). MonadIO m => Ptr ImVec2 -> m ()
Raw.setCursorPos

-- | Add an element to a ID stack
--
-- Read the FAQ (http://dearimgui.org/faq) for more details
-- about how ID are handled in dear imgui.
--
-- Those questions are answered and impacted by understanding of the ID stack system:
-- * "Q: Why is my widget not reacting when I click on it?"
-- * "Q: How can I have widgets with an empty label?"
-- * "Q: How can I have multiple widgets with the same label?"
--
-- Wraps @ImGui::PushId@ and @ImGui::PopId@
withID :: (MonadUnliftIO m, ToID id) => id -> m a -> m a
withID :: forall (m :: * -> *) id a.
(MonadUnliftIO m, ToID id) =>
id -> m a -> m a
withID id
i = m () -> m () -> m a -> m a
forall (m :: * -> *) a b c.
MonadUnliftIO m =>
m a -> m b -> m c -> m c
bracket_ (IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ id -> IO ()
forall a (m :: * -> *). (ToID a, MonadIO m) => a -> m ()
pushID id
i) m ()
forall (m :: * -> *). MonadIO m => m ()
Raw.popID

-- | A supplementary class to match overloaded functions in C++ the library.
class ToID a where
  pushID :: MonadIO m => a -> m ()

instance ToID CInt where
  pushID :: forall (m :: * -> *). MonadIO m => CInt -> m ()
pushID = CInt -> m ()
forall (m :: * -> *). MonadIO m => CInt -> m ()
Raw.pushIDInt

instance ToID Int where
  pushID :: forall (m :: * -> *). MonadIO m => Int -> m ()
pushID = CInt -> m ()
forall (m :: * -> *). MonadIO m => CInt -> m ()
Raw.pushIDInt (CInt -> m ()) -> (Int -> CInt) -> Int -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral

instance ToID Integer where
  pushID :: forall (m :: * -> *). MonadIO m => Integer -> m ()
pushID = CInt -> m ()
forall (m :: * -> *). MonadIO m => CInt -> m ()
Raw.pushIDInt (CInt -> m ()) -> (Integer -> CInt) -> Integer -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> CInt
forall a. Num a => Integer -> a
fromInteger

instance {-# OVERLAPPABLE #-} ToID (Ptr a) where
  pushID :: forall (m :: * -> *). MonadIO m => Ptr a -> m ()
pushID = Ptr a -> m ()
forall (m :: * -> *) a. MonadIO m => Ptr a -> m ()
Raw.pushIDPtr

instance {-# OVERLAPPING #-} ToID (Ptr CChar) where
  pushID :: forall (m :: * -> *). MonadIO m => CString -> m ()
pushID = CString -> m ()
forall (m :: * -> *). MonadIO m => CString -> m ()
Raw.pushIDStr

instance ToID (Ptr CChar, Int) where
  pushID :: forall (m :: * -> *). MonadIO m => CStringLen -> m ()
pushID = CStringLen -> m ()
forall (m :: * -> *). MonadIO m => CStringLen -> m ()
Raw.pushIDStrLen

instance ToID Text where
  pushID :: forall (m :: * -> *). MonadIO m => Text -> m ()
pushID Text
t = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Text -> (CStringLen -> IO ()) -> IO ()
forall a. Text -> (CStringLen -> IO a) -> IO a
Text.withCStringLen Text
t CStringLen -> IO ()
forall a (m :: * -> *). (ToID a, MonadIO m) => a -> m ()
pushID

withStyleColor :: (MonadUnliftIO m, HasGetter ref ImVec4) => ImGuiCol -> ref -> m a -> m a
withStyleColor :: forall (m :: * -> *) ref a.
(MonadUnliftIO m, HasGetter ref ImVec4) =>
ImGuiCol -> ref -> m a -> m a
withStyleColor ImGuiCol
color ref
ref =
  m () -> m () -> m a -> m a
forall (m :: * -> *) a b c.
MonadUnliftIO m =>
m a -> m b -> m c -> m c
bracket_ (ImGuiCol -> ref -> m ()
forall (m :: * -> *) ref.
(MonadIO m, HasGetter ref ImVec4) =>
ImGuiCol -> ref -> m ()
pushStyleColor ImGuiCol
color ref
ref) (CInt -> m ()
forall (m :: * -> *). MonadIO m => CInt -> m ()
Raw.popStyleColor CInt
1)

-- | 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, HasGetter ref ImVec4) => ImGuiCol -> ref -> m ()
pushStyleColor :: forall (m :: * -> *) ref.
(MonadIO m, HasGetter ref ImVec4) =>
ImGuiCol -> ref -> m ()
pushStyleColor ImGuiCol
col ref
colorRef = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  ImVec4
color <- ref -> IO ImVec4
forall t a (m :: * -> *). (HasGetter t a, MonadIO m) => t -> m a
get ref
colorRef
  ImVec4 -> (Ptr ImVec4 -> IO ()) -> IO ()
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with ImVec4
color \Ptr ImVec4
colorPtr ->
    ImGuiCol -> Ptr ImVec4 -> IO ()
forall (m :: * -> *). MonadIO m => ImGuiCol -> Ptr ImVec4 -> m ()
Raw.pushStyleColor ImGuiCol
col Ptr ImVec4
colorPtr

withStyleVar :: (MonadUnliftIO m, HasGetter ref ImVec2) => ImGuiStyleVar -> ref -> m a -> m a
withStyleVar :: forall (m :: * -> *) ref a.
(MonadUnliftIO m, HasGetter ref ImVec2) =>
ImGuiStyleVar -> ref -> m a -> m a
withStyleVar ImGuiStyleVar
style ref
ref =
  m () -> m () -> m a -> m a
forall (m :: * -> *) a b c.
MonadUnliftIO m =>
m a -> m b -> m c -> m c
bracket_ (ImGuiStyleVar -> ref -> m ()
forall (m :: * -> *) ref.
(MonadIO m, HasGetter ref ImVec2) =>
ImGuiStyleVar -> ref -> m ()
pushStyleVar ImGuiStyleVar
style ref
ref) (CInt -> m ()
forall (m :: * -> *). MonadIO m => CInt -> m ()
Raw.popStyleVar CInt
1)

-- | 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, HasGetter ref ImVec2) => ImGuiStyleVar -> ref -> m ()
pushStyleVar :: forall (m :: * -> *) ref.
(MonadIO m, HasGetter ref ImVec2) =>
ImGuiStyleVar -> ref -> m ()
pushStyleVar ImGuiStyleVar
style ref
valRef = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  ImVec2
val <- ref -> IO ImVec2
forall t a (m :: * -> *). (HasGetter t a, MonadIO m) => t -> m a
get ref
valRef
  ImVec2 -> (Ptr ImVec2 -> IO ()) -> IO ()
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with ImVec2
val \Ptr ImVec2
valPtr ->
    ImGuiStyleVar -> Ptr ImVec2 -> IO ()
forall (m :: * -> *).
MonadIO m =>
ImGuiStyleVar -> Ptr ImVec2 -> m ()
Raw.pushStyleVar ImGuiStyleVar
style Ptr ImVec2
valPtr

-- | Remove style variable modifications from the shared stack
--
-- Wraps @ImGui::PopStyleVar()@
popStyleVar :: (MonadIO m) => Int -> m ()
popStyleVar :: forall (m :: * -> *). MonadIO m => Int -> m ()
popStyleVar Int
n = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do
  CInt -> IO ()
forall (m :: * -> *). MonadIO m => CInt -> m ()
Raw.popStyleVar (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
n)

-- | Render widgets inside the block using provided font.
withFont :: MonadUnliftIO m => Raw.Font.Font -> m a -> m a
withFont :: forall (m :: * -> *) a. MonadUnliftIO m => Font -> m a -> m a
withFont Font
font = m () -> m () -> m a -> m a
forall (m :: * -> *) a b c.
MonadUnliftIO m =>
m a -> m b -> m c -> m c
bracket_ (Font -> m ()
forall (m :: * -> *). MonadIO m => Font -> m ()
Raw.Font.pushFont Font
font) m ()
forall (m :: * -> *). MonadIO m => m ()
Raw.Font.popFont

-- | Clips a large list of items
--
-- The requirements on @a@ are that they are all of the same height.
withListClipper :: (ClipItems t a, MonadUnliftIO m) => Maybe Float -> t a -> (a -> m ()) -> m ()
withListClipper :: forall (t :: * -> *) a (m :: * -> *).
(ClipItems t a, MonadUnliftIO m) =>
Maybe Float -> t a -> (a -> m ()) -> m ()
withListClipper Maybe Float
itemHeight t a
items a -> m ()
action =
  m (Ptr ImGuiListClipper)
-> (Ptr ImGuiListClipper -> m ())
-> (Ptr ImGuiListClipper -> m ())
-> m ()
forall (m :: * -> *) a b c.
MonadUnliftIO m =>
m a -> (a -> m b) -> (a -> m c) -> m c
bracket
    (IO (Ptr ImGuiListClipper) -> m (Ptr ImGuiListClipper)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Ptr ImGuiListClipper) -> m (Ptr ImGuiListClipper))
-> IO (Ptr ImGuiListClipper) -> m (Ptr ImGuiListClipper)
forall a b. (a -> b) -> a -> b
$ String -> IO (Ptr ImGuiListClipper) -> IO (Ptr ImGuiListClipper)
forall a. String -> IO (Ptr a) -> IO (Ptr a)
throwIfNull String
"withListClipper: ListClipper allocation failed" IO (Ptr ImGuiListClipper)
forall (m :: * -> *). MonadIO m => m (Ptr ImGuiListClipper)
Raw.ListClipper.new)
    Ptr ImGuiListClipper -> m ()
forall (m :: * -> *). MonadIO m => Ptr ImGuiListClipper -> m ()
Raw.ListClipper.delete
    Ptr ImGuiListClipper -> m ()
step
  where
    itemHeight' :: CFloat
itemHeight' = CFloat -> (Float -> CFloat) -> Maybe Float -> CFloat
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (-CFloat
1.0) Float -> CFloat
CFloat Maybe Float
itemHeight
    itemCount' :: CInt
itemCount' = CInt -> (Int -> CInt) -> Maybe Int -> CInt
forall b a. b -> (a -> b) -> Maybe a -> b
maybe CInt
forall a. Bounded a => a
maxBound Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (t a -> Maybe Int
forall (t :: * -> *) a. ClipItems t a => t a -> Maybe Int
itemCount t a
items)

    step :: Ptr ImGuiListClipper -> m ()
step Ptr ImGuiListClipper
clipper = do
      Ptr ImGuiListClipper -> CInt -> CFloat -> m ()
forall (m :: * -> *).
MonadIO m =>
Ptr ImGuiListClipper -> CInt -> CFloat -> m ()
Raw.ListClipper.begin Ptr ImGuiListClipper
clipper CInt
itemCount' CFloat
itemHeight'
      Ptr ImGuiListClipper -> m ()
go Ptr ImGuiListClipper
clipper

    go :: Ptr ImGuiListClipper -> m ()
go Ptr ImGuiListClipper
clipper = do
      Bool
doStep <- Ptr ImGuiListClipper -> m Bool
forall (m :: * -> *). MonadIO m => Ptr ImGuiListClipper -> m Bool
Raw.ListClipper.step Ptr ImGuiListClipper
clipper
      Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
doStep do
        let
          startIndex :: Int
startIndex = CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CInt -> Int) -> CInt -> Int
forall a b. (a -> b) -> a -> b
$ Ptr ImGuiListClipper -> CInt
Raw.ListClipper.displayStart Ptr ImGuiListClipper
clipper
          endIndex :: Int
endIndex   = CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CInt -> Int) -> CInt -> Int
forall a b. (a -> b) -> a -> b
$ Ptr ImGuiListClipper -> CInt
Raw.ListClipper.displayEnd Ptr ImGuiListClipper
clipper
        (a -> m ()) -> t a -> m ()
forall (t :: * -> *) a (m :: * -> *).
(ClipItems t a, Monad m) =>
(a -> m ()) -> t a -> m ()
stepItems a -> m ()
action (t a -> m ()) -> t a -> m ()
forall a b. (a -> b) -> a -> b
$
          Int -> Int -> t a -> t a
forall (t :: * -> *) a. ClipItems t a => Int -> Int -> t a -> t a
clipItems Int
startIndex Int
endIndex t a
items

        Ptr ImGuiListClipper -> m ()
go Ptr ImGuiListClipper
clipper

-- | Containers usable with 'ListClipper'.
class ClipItems t a where
  itemCount :: t a -> Maybe Int
  clipItems :: Int -> Int -> t a -> t a
  stepItems :: Monad m => (a -> m ()) -> t a -> m ()

-- | Unbounded stream of items.
instance ClipItems [] a where
  itemCount :: [a] -> Maybe Int
itemCount = Maybe Int -> [a] -> Maybe Int
forall a b. a -> b -> a
const Maybe Int
forall a. Maybe a
Nothing

  clipItems :: Int -> Int -> [a] -> [a]
clipItems Int
displayStart Int
displayEnd =
    Int -> [a] -> [a]
forall a. Int -> [a] -> [a]
take (Int
displayEnd Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
displayStart) ([a] -> [a]) -> ([a] -> [a]) -> [a] -> [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [a] -> [a]
forall a. Int -> [a] -> [a]
drop Int
displayStart

  stepItems :: forall (m :: * -> *). Monad m => (a -> m ()) -> [a] -> m ()
stepItems = (a -> m ()) -> [a] -> m ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_

instance ClipItems V.Vector a where
  itemCount :: Vector a -> Maybe Int
itemCount = Int -> Maybe Int
forall a. a -> Maybe a
Just (Int -> Maybe Int) -> (Vector a -> Int) -> Vector a -> Maybe Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Vector a -> Int
forall a. Vector a -> Int
V.length

  clipItems :: Int -> Int -> Vector a -> Vector a
clipItems Int
displayStart Int
displayEnd =
    Int -> Int -> Vector a -> Vector a
forall a. Int -> Int -> Vector a -> Vector a
V.slice Int
displayStart (Int
displayEnd Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
displayStart)

  stepItems :: forall (m :: * -> *). Monad m => (a -> m ()) -> Vector a -> m ()
stepItems = (a -> m ()) -> Vector a -> m ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> Vector a -> m ()
V.mapM_

instance Storable a => ClipItems VS.Vector a where
  itemCount :: Vector a -> Maybe Int
itemCount = Int -> Maybe Int
forall a. a -> Maybe a
Just (Int -> Maybe Int) -> (Vector a -> Int) -> Vector a -> Maybe Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Vector a -> Int
forall a. Storable a => Vector a -> Int
VS.length

  clipItems :: Int -> Int -> Vector a -> Vector a
clipItems Int
displayStart Int
displayEnd =
    Int -> Int -> Vector a -> Vector a
forall a. Storable a => Int -> Int -> Vector a -> Vector a
VS.slice Int
displayStart (Int
displayEnd Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
displayStart)

  stepItems :: forall (m :: * -> *). Monad m => (a -> m ()) -> Vector a -> m ()
stepItems = (a -> m ()) -> Vector a -> m ()
forall (m :: * -> *) a b.
(Monad m, Storable a) =>
(a -> m b) -> Vector a -> m ()
VS.mapM_

instance VU.Unbox a => ClipItems VU.Vector a where
  itemCount :: Vector a -> Maybe Int
itemCount = Int -> Maybe Int
forall a. a -> Maybe a
Just (Int -> Maybe Int) -> (Vector a -> Int) -> Vector a -> Maybe Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Vector a -> Int
forall a. Unbox a => Vector a -> Int
VU.length

  clipItems :: Int -> Int -> Vector a -> Vector a
clipItems Int
displayStart Int
displayEnd =
    Int -> Int -> Vector a -> Vector a
forall a. Unbox a => Int -> Int -> Vector a -> Vector a
VU.slice Int
displayStart (Int
displayEnd Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
displayStart)

  stepItems :: forall (m :: * -> *). Monad m => (a -> m ()) -> Vector a -> m ()
stepItems = (a -> m ()) -> Vector a -> m ()
forall (m :: * -> *) a b.
(Monad m, Unbox a) =>
(a -> m b) -> Vector a -> m ()
VU.mapM_

-- | ClipList helper for arbitrary unmaterialized ranges.
data ClipRange a = ClipRange a a
  deriving (ClipRange a -> ClipRange a -> Bool
(ClipRange a -> ClipRange a -> Bool)
-> (ClipRange a -> ClipRange a -> Bool) -> Eq (ClipRange a)
forall a. Eq a => ClipRange a -> ClipRange a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ClipRange a -> ClipRange a -> Bool
$c/= :: forall a. Eq a => ClipRange a -> ClipRange a -> Bool
== :: ClipRange a -> ClipRange a -> Bool
$c== :: forall a. Eq a => ClipRange a -> ClipRange a -> Bool
Eq, Eq (ClipRange a)
Eq (ClipRange a)
-> (ClipRange a -> ClipRange a -> Ordering)
-> (ClipRange a -> ClipRange a -> Bool)
-> (ClipRange a -> ClipRange a -> Bool)
-> (ClipRange a -> ClipRange a -> Bool)
-> (ClipRange a -> ClipRange a -> Bool)
-> (ClipRange a -> ClipRange a -> ClipRange a)
-> (ClipRange a -> ClipRange a -> ClipRange a)
-> Ord (ClipRange a)
ClipRange a -> ClipRange a -> Bool
ClipRange a -> ClipRange a -> Ordering
ClipRange a -> ClipRange a -> ClipRange a
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall {a}. Ord a => Eq (ClipRange a)
forall a. Ord a => ClipRange a -> ClipRange a -> Bool
forall a. Ord a => ClipRange a -> ClipRange a -> Ordering
forall a. Ord a => ClipRange a -> ClipRange a -> ClipRange a
min :: ClipRange a -> ClipRange a -> ClipRange a
$cmin :: forall a. Ord a => ClipRange a -> ClipRange a -> ClipRange a
max :: ClipRange a -> ClipRange a -> ClipRange a
$cmax :: forall a. Ord a => ClipRange a -> ClipRange a -> ClipRange a
>= :: ClipRange a -> ClipRange a -> Bool
$c>= :: forall a. Ord a => ClipRange a -> ClipRange a -> Bool
> :: ClipRange a -> ClipRange a -> Bool
$c> :: forall a. Ord a => ClipRange a -> ClipRange a -> Bool
<= :: ClipRange a -> ClipRange a -> Bool
$c<= :: forall a. Ord a => ClipRange a -> ClipRange a -> Bool
< :: ClipRange a -> ClipRange a -> Bool
$c< :: forall a. Ord a => ClipRange a -> ClipRange a -> Bool
compare :: ClipRange a -> ClipRange a -> Ordering
$ccompare :: forall a. Ord a => ClipRange a -> ClipRange a -> Ordering
Ord, Int -> ClipRange a -> ShowS
[ClipRange a] -> ShowS
ClipRange a -> String
(Int -> ClipRange a -> ShowS)
-> (ClipRange a -> String)
-> ([ClipRange a] -> ShowS)
-> Show (ClipRange a)
forall a. Show a => Int -> ClipRange a -> ShowS
forall a. Show a => [ClipRange a] -> ShowS
forall a. Show a => ClipRange a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ClipRange a] -> ShowS
$cshowList :: forall a. Show a => [ClipRange a] -> ShowS
show :: ClipRange a -> String
$cshow :: forall a. Show a => ClipRange a -> String
showsPrec :: Int -> ClipRange a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> ClipRange a -> ShowS
Show)

instance (Ord a, Enum a, Num a) => ClipItems ClipRange a where
  itemCount :: ClipRange a -> Maybe Int
itemCount (ClipRange a
_begin a
end) =
    Int -> Maybe Int
forall a. a -> Maybe a
Just (Int -> Maybe Int) -> Int -> Maybe Int
forall a b. (a -> b) -> a -> b
$ a -> Int
forall a. Enum a => a -> Int
fromEnum a
end

  clipItems :: Int -> Int -> ClipRange a -> ClipRange a
clipItems Int
clipBegin Int
clipEnd (ClipRange a
oldBegin a
oldEnd) =
    a -> a -> ClipRange a
forall a. a -> a -> ClipRange a
ClipRange
      (Int -> a
forall a. Enum a => Int -> a
toEnum (Int -> a) -> Int -> a
forall a b. (a -> b) -> a -> b
$ Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
clipBegin (Int -> Int) -> Int -> Int
forall a b. (a -> b) -> a -> b
$ a -> Int
forall a. Enum a => a -> Int
fromEnum a
oldBegin)
      (Int -> a
forall a. Enum a => Int -> a
toEnum (Int -> a) -> Int -> a
forall a b. (a -> b) -> a -> b
$ Int -> Int -> Int
forall a. Ord a => a -> a -> a
min Int
clipEnd (Int -> Int) -> Int -> Int
forall a b. (a -> b) -> a -> b
$ a -> Int
forall a. Enum a => a -> Int
fromEnum a
oldEnd)

  stepItems :: forall (m :: * -> *). Monad m => (a -> m ()) -> ClipRange a -> m ()
stepItems a -> m ()
action (ClipRange a
start a
end) =
    (a -> m ()) -> [a] -> m ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ a -> m ()
action [a
start .. a
end a -> a -> a
forall a. Num a => a -> a -> a
- a
1]