dear-imgui-2.0.0: Haskell bindings for Dear ImGui.
Safe HaskellSafe-Inferred
LanguageHaskell2010

DearImGui

Description

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

Synopsis

Context Creation and Access

newtype Context Source #

Wraps ImGuiContext*.

Constructors

Context (Ptr ImGuiContext) 

createContext :: MonadIO m => m Context Source #

Wraps ImGui::CreateContext().

destroyContext :: MonadIO m => Context -> m () Source #

Wraps ImGui::DestroyContext().

getCurrentContext :: MonadIO m => m Context Source #

Wraps ImGui::GetCurrentContext().

setCurrentContext :: MonadIO m => Context -> m () Source #

Wraps ImGui::SetCurrentContext().

Main

newFrame :: MonadIO m => m () Source #

Start a new Dear ImGui frame, you can submit any command from this point until render/endFrame.

Wraps ImGui::NewFrame().

endFrame :: MonadIO m => m () Source #

Ends the Dear ImGui frame. automatically called by render. If you don't need to render data (skipping rendering) you may call endFrame without render... but you'll have wasted CPU already! If you don't need to render, better to not create any windows and not call newFrame at all!

render :: MonadIO m => m () Source #

Ends the Dear ImGui frame, finalize the draw data. You can then get call getDrawData.

newtype DrawData Source #

Wraps ImDrawData*.

Constructors

DrawData (Ptr ()) 

getDrawData :: MonadIO m => m DrawData Source #

Valid after render and until the next call to newFrame. This is what you have to render.

checkVersion :: MonadIO m => m () Source #

Wraps IMGUI_CHECKVERSION()

Demo, Debug, Information

showDemoWindow :: MonadIO m => m () Source #

Create demo window. Demonstrate most ImGui features. Call this to learn about the library! Try to make it always available in your application!

showMetricsWindow :: MonadIO m => m () Source #

Create Metrics/Debugger window. Display Dear ImGui internals: windows, draw commands, various internal state, etc.

showAboutWindow :: MonadIO m => m () Source #

Create About window. display Dear ImGui version, credits and build/system information.

showUserGuide :: MonadIO m => m () Source #

Add basic help/info block (not a window): how to manipulate ImGui as a end-user (mouse/keyboard controls).

getVersion :: MonadIO m => m Text Source #

Get the compiled version string e.g. "1.80 WIP" (essentially the value for IMGUI_VERSION from the compiled version of imgui.cpp).

Styles

styleColorsDark :: MonadIO m => m () Source #

New, recommended style (default).

Wraps ImGui::StyleColorsDark().

styleColorsLight :: MonadIO m => m () Source #

Best used with borders and a custom, thicker font.

Wraps ImGui::StyleColorsLight().

styleColorsClassic :: MonadIO m => m () Source #

Classic ImGui style.

Wraps ImGui::StyleColorsClasic().

Windows

withWindow :: MonadUnliftIO m => Text -> (Bool -> m a) -> m a Source #

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.

withWindowOpen :: MonadUnliftIO m => Text -> m () -> m () Source #

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.

withFullscreen :: MonadUnliftIO m => m () -> m () Source #

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.

begin :: MonadIO m => Text -> m Bool Source #

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.

end :: MonadIO m => m () Source #

Pop window from the stack.

Wraps ImGui::End().

Utilities

getWindowDrawList :: MonadIO m => m DrawList Source #

Get draw list associated to the current window.

getWindowPos :: MonadIO m => m ImVec2 Source #

Get current window position in screen space.

Useful if you want to do your own drawing via the DrawList API.

Manipulation

setNextWindowPos :: (MonadIO m, HasGetter ref ImVec2) => ref -> ImGuiCond -> Maybe ref -> m () Source #

Set next window position. Call before begin Use pivot=(0.5,0.5) to center on given point, etc.

Wraps ImGui::SetNextWindowPos()

setNextWindowSize :: (MonadIO m, HasGetter ref ImVec2) => ref -> ImGuiCond -> m () Source #

Set next window size. Call before begin

Wraps ImGui::SetNextWindowSize()

setNextWindowFullscreen :: MonadIO m => m () Source #

Set next window size and position to match current display size.

Call before begin.

Wraps ImGui::SetNextWindowPos(), ImGui::SetNextWindowSize()

setNextWindowContentSize :: (MonadIO m, HasGetter ref ImVec2) => ref -> m () Source #

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

setNextWindowSizeConstraints :: (MonadIO m, HasGetter ref ImVec2) => ref -> ref -> m () Source #

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

setNextWindowCollapsed :: MonadIO m => Bool -> ImGuiCond -> m () Source #

Set next window collapsed state. call before begin

Wraps ImGui::SetNextWindowCollapsed()

setNextWindowBgAlpha :: MonadIO m => Float -> m () Source #

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

Child Windows

withChild :: MonadUnliftIO m => Text -> ImVec2 -> Bool -> ImGuiWindowFlags -> (Bool -> m a) -> m a Source #

Action wrapper for child windows.

Action will get False if the child region is collapsed or fully clipped.

withChildOpen :: MonadUnliftIO m => Text -> ImVec2 -> Bool -> ImGuiWindowFlags -> m () -> m () Source #

Action-skipping wrapper for child windows.

Action will be skipped if the child region is collapsed or fully clipped.

withChildContext :: MonadUnliftIO m => Text -> (Bool -> m a) -> m a Source #

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.

beginChild :: MonadIO m => Text -> ImVec2 -> Bool -> ImGuiWindowFlags -> m Bool Source #

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

endChild :: MonadIO m => m () Source #

Wraps ImGui::EndChild().

Parameter stacks

withStyleColor :: (MonadUnliftIO m, HasGetter ref ImVec4) => ImGuiCol -> ref -> m a -> m a Source #

pushStyleColor :: (MonadIO m, HasGetter ref ImVec4) => ImGuiCol -> ref -> m () Source #

Modify a style color by pushing to the shared stack.

Always use this if you modify the style after newFrame.

Wraps ImGui::PushStyleColor()

popStyleColor :: MonadIO m => CInt -> m () Source #

Remove style color modifications from the shared stack

Wraps ImGui::PopStyleColor()

withStyleVar :: (MonadUnliftIO m, HasGetter ref ImVec2) => ImGuiStyleVar -> ref -> m a -> m a Source #

pushStyleVar :: (MonadIO m, HasGetter ref ImVec2) => ImGuiStyleVar -> ref -> m () Source #

Modify a style variable by pushing to the shared stack.

Always use this if you modify the style after newFrame.

Wraps ImGui::PushStyleVar()

popStyleVar :: MonadIO m => Int -> m () Source #

Remove style variable modifications from the shared stack

Wraps ImGui::PopStyleVar()

withFont :: MonadUnliftIO m => Font -> m a -> m a Source #

Render widgets inside the block using provided font.

pushFont :: MonadIO m => Font -> m () Source #

Pushes a font into the parameters stack, so ImGui would render following text using it.

popFont :: MonadIO m => m () Source #

Pops a font pushed into the parameters stack

Should be called only after a corresponding pushFont call.

data Font Source #

Font runtime data handle

Wraps ImFont*.

Cursor/Layout

separator :: MonadIO m => m () Source #

Separator, generally horizontal. inside a menu bar or in horizontal layout mode, this becomes a vertical separator.

Wraps ImGui::Separator()

sameLine :: MonadIO m => m () Source #

Call between widgets or groups to layout them horizontally.

Wraps ImGui::SameLine.

newLine :: MonadIO m => m () Source #

undo a sameLine or force a new line when in an horizontal-layout context.

Wraps ImGui::NewLine()

spacing :: MonadIO m => m () Source #

Add vertical spacing.

Wraps ImGui::Spacing()

dummy :: (MonadIO m, HasGetter ref ImVec2) => ref -> m () Source #

Add a dummy item of given size. unlike invisibleButton, dummy won't take the mouse click or be navigable into.

Wraps ImGui::Dummy()

withIndent :: MonadUnliftIO m => Float -> m a -> m a Source #

indent :: MonadIO m => Float -> m () Source #

Move content position toward the right, by indent_w, or style.IndentSpacing if indent_w <= 0

Wraps ImGui::Indent()

unindent :: MonadIO m => Float -> m () Source #

Move content position back to the left, by indent_w, or style.IndentSpacing if indent_w <= 0

Wraps ImGui::Unindent()

setNextItemWidth :: MonadIO m => Float -> m () Source #

Affect large frame+labels widgets only.

Wraps ImGui::SetNextItemWidth()

withItemWidth :: MonadUnliftIO m => Float -> m a -> m a Source #

withGroup :: MonadUnliftIO m => m a -> m a Source #

Lock horizontal starting position

Wraps ImGui::BeginGroup() and ImGui::EndGroup()

beginGroup :: MonadIO m => m () Source #

lock horizontal starting position

Wraps ImGui::BeginGroup()

endGroup :: MonadIO m => m () Source #

unlock horizontal starting position + capture the whole group bounding box into one "item" (so you can use isItemHovered or layout primitives such as sameLine on whole group, etc.)

Wraps ImGui::EndGroup()

setCursorPos :: (MonadIO m, HasGetter ref ImVec2) => ref -> m () Source #

Set cursor position in window-local coordinates

Wraps ImGui::SetCursorPos()

alignTextToFramePadding :: MonadIO m => m () Source #

Vertically align upcoming text baseline to FramePadding.y so that it will align properly to regularly framed items (call if you have text on a line before a framed item)

Wraps ImGui::AlignTextToFramePadding()

ID stack

withID :: (MonadUnliftIO m, ToID id) => id -> m a -> m a Source #

Add an element to a ID stack

Read the FAQ (http:/dearimgui.orgfaq) 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

class ToID a where Source #

A supplementary class to match overloaded functions in C++ the library.

Methods

pushID :: MonadIO m => a -> m () Source #

Instances

Instances details
ToID CInt Source # 
Instance details

Defined in DearImGui

Methods

pushID :: MonadIO m => CInt -> m () Source #

ToID Text Source # 
Instance details

Defined in DearImGui

Methods

pushID :: MonadIO m => Text -> m () Source #

ToID Integer Source # 
Instance details

Defined in DearImGui

Methods

pushID :: MonadIO m => Integer -> m () Source #

ToID Int Source # 
Instance details

Defined in DearImGui

Methods

pushID :: MonadIO m => Int -> m () Source #

ToID (Ptr CChar) Source # 
Instance details

Defined in DearImGui

Methods

pushID :: MonadIO m => Ptr CChar -> m () Source #

ToID (Ptr a) Source # 
Instance details

Defined in DearImGui

Methods

pushID :: MonadIO m => Ptr a -> m () Source #

ToID (Ptr CChar, Int) Source # 
Instance details

Defined in DearImGui

Methods

pushID :: MonadIO m => (Ptr CChar, Int) -> m () Source #

Widgets

Text

text :: MonadIO m => Text -> m () Source #

Plain text.

textColored :: (HasGetter ref ImVec4, MonadIO m) => ref -> Text -> m () Source #

Colored text.

textDisabled :: MonadIO m => Text -> m () Source #

Plain text in a "disabled" color according to current style.

textWrapped :: MonadIO m => Text -> m () Source #

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.

labelText :: MonadIO m => Text -> Text -> m () Source #

Label+text combo aligned to other label+value widgets.

bulletText :: MonadIO m => Text -> m () Source #

Text with a little bullet aligned to the typical tree node.

Main

button :: MonadIO m => Text -> m Bool Source #

A button. Returns True when clicked.

Wraps ImGui::Button().

smallButton :: MonadIO m => Text -> m Bool Source #

Button with FramePadding=(0,0) to easily embed within text.

Wraps ImGui::SmallButton().

invisibleButton :: MonadIO m => Text -> ImVec2 -> ImGuiButtonFlags -> m Bool Source #

Flexible button behavior without the visuals.

Frequently useful to build custom behaviors using the public api (along with IsItemActive, IsItemHovered, etc).

Wraps ImGui::InvisibleButton().

arrowButton :: MonadIO m => Text -> ImGuiDir -> m Bool Source #

Square button with an arrow shape.

Wraps ImGui::ArrowButton().

image :: MonadIO m => Ptr () -> Ptr ImVec2 -> Ptr ImVec2 -> Ptr ImVec2 -> Ptr ImVec4 -> Ptr ImVec4 -> m () Source #

Image Area to draw a texture.

For OpenGL: The userTextureIDPtr points to the texture memory (eg. 0x0000000000000001)

See examplessdlImage.hs for the whole process.

Wraps ImGui::Image().

checkbox :: (HasSetter ref Bool, HasGetter ref Bool, MonadIO m) => Text -> ref -> m Bool Source #

Wraps ImGui::Checkbox().

bullet :: MonadIO m => m () Source #

Draw a small circle + keep the cursor on the same line. Advance cursor x position by getTreeNodeToLabelSpacing, same distance that treeNode uses.

Combo Box

withCombo :: MonadUnliftIO m => Text -> Text -> (Bool -> m a) -> m a Source #

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.

withComboOpen :: MonadUnliftIO m => Text -> Text -> m () -> m () Source #

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.

beginCombo :: MonadIO m => Text -> Text -> m Bool Source #

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

endCombo :: MonadIO m => m () Source #

Only call endCombo if beginCombo returns True!

Wraps ImGui::EndCombo().

combo :: (MonadIO m, HasGetter ref Int, HasSetter ref Int) => Text -> ref -> [Text] -> m Bool Source #

Wraps ImGui::Combo().

Drag Sliders

dragFloat :: (MonadIO m, HasSetter ref Float, HasGetter ref Float) => Text -> ref -> Float -> Float -> Float -> m Bool Source #

Wraps ImGui::DragFloat()

dragFloat2 :: (MonadIO m, HasSetter ref (Float, Float), HasGetter ref (Float, Float)) => Text -> ref -> Float -> Float -> Float -> m Bool Source #

Wraps ImGui::DragFloat2()

dragFloat3 :: (MonadIO m, HasSetter ref (Float, Float, Float), HasGetter ref (Float, Float, Float)) => Text -> ref -> Float -> Float -> Float -> m Bool Source #

Wraps ImGui::DragFloat3()

dragFloat4 :: (MonadIO m, HasSetter ref (Float, Float, Float, Float), HasGetter ref (Float, Float, Float, Float)) => Text -> ref -> Float -> Float -> Float -> m Bool Source #

Wraps ImGui::DragFloat4()

dragFloatRange2 :: (MonadIO m, HasSetter ref Float, HasGetter ref Float) => Text -> ref -> ref -> Float -> Float -> Float -> Text -> Text -> m Bool Source #

dragInt :: (MonadIO m, HasSetter ref Int, HasGetter ref Int) => Text -> ref -> Float -> Int -> Int -> m Bool Source #

Wraps ImGui::DragFloat()

dragInt2 :: (MonadIO m, HasSetter ref (Int, Int), HasGetter ref (Int, Int)) => Text -> ref -> Float -> Int -> Int -> m Bool Source #

Wraps ImGui::DragInt2()

dragInt3 :: (MonadIO m, HasSetter ref (Int, Int, Int), HasGetter ref (Int, Int, Int)) => Text -> ref -> Float -> Int -> Int -> m Bool Source #

Wraps ImGui::DragInt3()

dragInt4 :: (MonadIO m, HasSetter ref (Int, Int, Int, Int), HasGetter ref (Int, Int, Int, Int)) => Text -> ref -> Float -> Int -> Int -> m Bool Source #

Wraps ImGui::DragInt4()

dragIntRange2 :: (MonadIO m, HasSetter ref Int, HasGetter ref Int) => Text -> ref -> ref -> Float -> Int -> Int -> Text -> Text -> m Bool Source #

dragScalar :: (HasSetter ref a, HasGetter ref a, HasGetter range a, Storable a, MonadIO m) => Text -> ImGuiDataType -> ref -> Float -> range -> range -> Text -> ImGuiSliderFlags -> m Bool Source #

dragScalarN :: (HasSetter ref [a], HasGetter ref [a], HasGetter range a, Storable a, MonadIO m) => Text -> ImGuiDataType -> ref -> Float -> range -> range -> Text -> ImGuiSliderFlags -> m Bool Source #

Slider

sliderFloat :: (MonadIO m, HasSetter ref Float, HasGetter ref Float) => Text -> ref -> Float -> Float -> m Bool Source #

Wraps ImGui::SliderFloat()

sliderFloat2 :: (MonadIO m, HasSetter ref (Float, Float), HasGetter ref (Float, Float)) => Text -> ref -> Float -> Float -> m Bool Source #

Wraps ImGui::SliderFloat2()

sliderFloat3 :: (MonadIO m, HasSetter ref (Float, Float, Float), HasGetter ref (Float, Float, Float)) => Text -> ref -> Float -> Float -> m Bool Source #

Wraps ImGui::SliderFloat3()

sliderFloat4 :: (MonadIO m, HasSetter ref (Float, Float, Float, Float), HasGetter ref (Float, Float, Float, Float)) => Text -> ref -> Float -> Float -> m Bool Source #

Wraps ImGui::SliderFloat4()

sliderAngle :: (MonadIO m, HasSetter ref Float, HasGetter ref Float) => Text -> ref -> Float -> Float -> m Bool Source #

Slider widget to select an angle in radians, while displaying degrees.

sliderInt :: (MonadIO m, HasSetter ref Int, HasGetter ref Int) => Text -> ref -> Int -> Int -> m Bool Source #

Wraps ImGui::SliderInt()

sliderInt2 :: (MonadIO m, HasSetter ref (Int, Int), HasGetter ref (Int, Int)) => Text -> ref -> Int -> Int -> m Bool Source #

Wraps ImGui::SliderInt2()

sliderInt3 :: (MonadIO m, HasSetter ref (Int, Int, Int), HasGetter ref (Int, Int, Int)) => Text -> ref -> Int -> Int -> m Bool Source #

Wraps ImGui::SliderInt3()

sliderInt4 :: (MonadIO m, HasSetter ref (Int, Int, Int, Int), HasGetter ref (Int, Int, Int, Int)) => Text -> ref -> Int -> Int -> m Bool Source #

Wraps ImGui::SliderInt4()

sliderScalar :: (HasGetter ref a, HasSetter ref a, HasGetter range a, Storable a, MonadIO m) => Text -> ImGuiDataType -> ref -> range -> range -> Text -> ImGuiSliderFlags -> m Bool Source #

sliderScalarN :: (HasSetter value [a], HasGetter value [a], HasGetter range a, Storable a, MonadIO m) => Text -> ImGuiDataType -> value -> range -> range -> Text -> ImGuiSliderFlags -> m Bool Source #

vSliderFloat :: (HasSetter ref Float, HasGetter ref Float, MonadIO m) => Text -> ImVec2 -> ref -> Float -> Float -> m Bool Source #

vSliderInt :: (HasSetter ref Int, HasGetter ref Int, MonadIO m) => Text -> ImVec2 -> ref -> Int -> Int -> m Bool Source #

vSliderScalar :: (HasSetter ref a, HasGetter ref a, HasGetter range a, Storable a, MonadIO m) => Text -> ImVec2 -> ImGuiDataType -> ref -> range -> range -> Text -> ImGuiSliderFlags -> m Bool Source #

Text Input

inputText :: (MonadIO m, HasSetter ref Text, HasGetter ref Text) => Text -> ref -> Int -> m Bool Source #

Wraps ImGui::InputText().

inputTextMultiline :: (MonadIO m, HasSetter ref Text, HasGetter ref Text) => Text -> ref -> Int -> ImVec2 -> m Bool Source #

Wraps ImGui::InputTextMultiline().

inputTextWithHint :: (MonadIO m, HasSetter ref Text, HasGetter ref Text) => Text -> Text -> ref -> Int -> m Bool Source #

Wraps ImGui::InputTextWithHint().

Color Editor/Picker

colorPicker3 :: (MonadIO m, HasSetter ref ImVec3, HasGetter ref ImVec3) => Text -> ref -> m Bool Source #

Wraps ImGui::ColorPicker3().

colorButton :: (MonadIO m, HasSetter ref ImVec4, HasGetter ref ImVec4) => Text -> ref -> m Bool Source #

Display a color square/button, hover for details, return true when pressed.

Wraps ImGui::ColorButton().

Tables

withTable :: MonadUnliftIO m => TableOptions -> Text -> Int -> (Bool -> m a) -> m a Source #

Create a table.

The action will get False if the entry is not visible.

Example usage:

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

withTableOpen :: MonadUnliftIO m => TableOptions -> Text -> Int -> m () -> m () Source #

data TableOptions Source #

Instances

Instances details
Show TableOptions Source # 
Instance details

Defined in DearImGui

beginTable :: MonadIO m => TableOptions -> Text -> Int -> m Bool Source #

Wraps ImGui::BeginTable().

endTable :: MonadIO m => m () Source #

Only call endTable if beginTable returns true!

Wraps ImGui::EndTable().

Setup

tableSetupColumn :: MonadIO m => Text -> m () Source #

Wraps ImGui::TableSetupColumn() using defTableColumnOptions.

tableSetupColumnWith :: MonadIO m => TableColumnOptions -> Text -> m () Source #

Wraps ImGui::TableSetupColumn() with explicit options.

tableHeadersRow :: MonadIO m => m () Source #

Wraps ImGui::TableHeadersRow(). submit all headers cells based on data provided to tableSetupColumn + submit context menu

tableHeader :: MonadIO m => CString -> m () Source #

Wraps ImGui::TableHeader(). submit one header cell manually (rarely used)

tableSetupScrollFreeze :: MonadIO m => Int -> Int -> m () Source #

Wraps ImGui::TableSetupScrollFreeze(). lock columns/rows so they stay visible when scrolled.

Rows

tableNextRow :: MonadIO m => m () Source #

Wraps ImGui::TableNextRow() with defTableRowOptions. append into the first cell of a new row.

tableNextRowWith :: MonadIO m => TableRowOptions -> m () Source #

Wraps ImGui::TableNextRow() with explicit options.

Columns

tableNextColumn :: MonadIO m => m () -> m () Source #

tableSetColumnIndex :: MonadIO m => Int -> m Bool Source #

Wraps ImGui::TableSetColumnIndex(). append into the specified column. Return true when column is visible.

Sorting

withSortableTable :: MonadIO m => (Bool -> [TableSortingSpecs] -> m ()) -> m () Source #

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:

Expand
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

Queries

tableGetColumnCount :: MonadIO m => m Int Source #

Wraps ImGui::TableGetColumnCount(). return number of columns (value passed to BeginTable)

tableGetColumnIndex :: MonadIO m => m Int Source #

Wraps ImGui::TableGetColumnIndex(). return current column index.

tableGetRowIndex :: MonadIO m => m Int Source #

Wraps ImGui::TableGetRowIndex(). return current row index

tableGetColumnName :: MonadIO m => Maybe Int -> m Text Source #

Wraps @ImGui::TableGetColumnName returns "" if column didn't have a name declared by TableSetupColumn Nothing returns the current column name

tableGetColumnFlags :: MonadIO m => Maybe Int -> m ImGuiTableColumnFlags Source #

Wraps ImGui::TableGetRowIndex(). return column flags so you can query their EnabledVisibleSorted/Hovered status flags. Nothing returns the current column flags

tableSetColumnEnabled :: MonadIO m => Int -> Bool -> m () Source #

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)

tableSetBgColor :: MonadIO m => ImGuiTableBgTarget -> ImU32 -> Maybe Int -> m () Source #

Wraps ImGui::TableSetBgColor(). change the color of a cell, row, or column. See ImGuiTableBgTarget flags for details. Nothing sets the current row/column color

Trees

treeNode :: MonadIO m => Text -> m Bool Source #

Wraps ImGui::TreeNode().

treePush :: MonadIO m => Text -> m () Source #

Wraps ImGui::TreePush().

treePop :: MonadIO m => m () Source #

Wraps ImGui::TreePop().

Selectables

selectable :: MonadIO m => Text -> m Bool Source #

Wraps ImGui::Selectable() with default options.

selectableWith :: MonadIO m => SelectableOptions -> Text -> m Bool Source #

Wraps ImGui::Selectable() with explicit options.

List Boxes

listBox :: (MonadIO m, HasGetter ref Int, HasSetter ref Int) => Text -> ref -> [Text] -> m Bool Source #

Data Plotting

plotHistogram :: MonadIO m => Text -> [CFloat] -> m () Source #

Wraps ImGui::PlotHistogram().

Menus

withMenuBar :: MonadUnliftIO m => (Bool -> m a) -> m a Source #

Append items to a window with MenuBar flag.

The action will get False if the menu is not visible.

withMenuBarOpen :: MonadUnliftIO m => m () -> m () Source #

Append items to a window with MenuBar flag.

The action will be skipped if the menu is not visible.

beginMenuBar :: MonadIO m => m Bool Source #

Append to menu-bar of current window (requires ImGuiWindowFlagsMenuBar flag set on parent window).

Wraps ImGui::BeginMenuBar().

endMenuBar :: MonadIO m => m () Source #

Only call endMenuBar if beginMenuBar returns true!

Wraps ImGui::EndMenuBar().

withMainMenuBar :: MonadUnliftIO m => (Bool -> m a) -> m a Source #

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.

withMainMenuBarOpen :: MonadUnliftIO m => m () -> m () Source #

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.

beginMainMenuBar :: MonadIO m => m Bool Source #

Create and append to a full screen menu-bar.

Wraps ImGui::BeginMainMenuBar().

endMainMenuBar :: MonadIO m => m () Source #

Only call endMainMenuBar if beginMainMenuBar returns true!

Wraps ImGui::EndMainMenuBar().

withMenu :: MonadUnliftIO m => Text -> (Bool -> m a) -> m a Source #

Create a sub-menu entry.

The action will get False if the entry is not visible.

withMenuOpen :: MonadUnliftIO m => Text -> m () -> m () Source #

Create a sub-menu entry.

The action will be skipped if the entry is not visible.

beginMenu :: MonadIO m => Text -> m Bool Source #

Create a sub-menu entry.

Wraps ImGui::BeginMenu().

endMenu :: MonadIO m => m () Source #

Only call endMenu if beginMenu returns true!

Wraps ImGui::EndMenu().

menuItem :: MonadIO m => Text -> m Bool Source #

Return true when activated. Shortcuts are displayed for convenience but not processed by ImGui at the moment

Wraps ImGui::MenuItem()

Tabs, tab bar

withTabBar :: MonadUnliftIO m => Text -> ImGuiTabBarFlags -> (Bool -> m a) -> m a Source #

Create a TabBar and start appending to it.

The action will get False if the Tab bar is not visible.

withTabBarOpen :: MonadUnliftIO m => Text -> ImGuiTabBarFlags -> m () -> m () Source #

Create a TabBar and start appending to it.

The action will be skipped if the Tab bar is not visible.

beginTabBar :: MonadIO m => Text -> ImGuiTabBarFlags -> m Bool Source #

Create a TabBar and start appending to it.

Wraps ImGui::BeginTabBar.

endTabBar :: MonadIO m => m () Source #

Finish appending elements to a tab bar. Only call if beginTabBar returns True.

Wraps ImGui::EndTabBar.

withTabItem :: (MonadUnliftIO m, HasGetter ref Bool, HasSetter ref Bool) => Text -> ref -> ImGuiTabBarFlags -> (Bool -> m a) -> m a Source #

Create a new tab.

The action will get True if the tab is selected.

withTabItemOpen :: (MonadUnliftIO m, HasGetter ref Bool, HasSetter ref Bool) => Text -> ref -> ImGuiTabBarFlags -> m () -> m () Source #

Create a new tab.

The action will be skipped unless the tab is selected.

beginTabItem :: (MonadIO m, HasGetter ref Bool, HasSetter ref Bool) => Text -> ref -> ImGuiTabBarFlags -> m Bool Source #

Create a new tab. Returns True if the tab is selected.

Wraps ImGui::BeginTabItem.

endTabItem :: MonadIO m => m () Source #

Finish appending elements to a tab. Only call if beginTabItem returns True.

Wraps ImGui::EndTabItem.

tabItemButton :: MonadIO m => Text -> ImGuiTabItemFlags -> m Bool Source #

Create a tab that behaves like a button. Returns True when clicked. Cannot be selected in the tab bar.

Wraps ImGui.TabItemButton.

setTabItemClosed :: MonadIO m => Text -> m () Source #

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.

Tooltips

withTooltip :: MonadUnliftIO m => m a -> m a Source #

Create a tooltip.

Those are windows that follow a mouse and don't take focus away. Can contain any kind of items.

beginTooltip :: MonadIO m => m () Source #

Begin/append a tooltip window to create full-featured tooltip (with any kind of items).

Wraps ImGui::BeginTooltip()

endTooltip :: MonadIO m => m () Source #

Wraps ImGui::EndTooltip()

Popups/Modals

Generic

withPopup :: MonadUnliftIO m => Text -> (Bool -> m a) -> m a Source #

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.

withPopupOpen :: MonadUnliftIO m => Text -> m () -> m () Source #

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.

beginPopup :: MonadIO m => Text -> m Bool Source #

Returns True if the popup is open, and you can start outputting to it.

Wraps ImGui::BeginPopup()

endPopup :: MonadIO m => m () Source #

Only call endPopup if beginPopup or beginPopupModal returns True!

Wraps ImGui::BeginPopupModal()

Modal

withPopupModal :: MonadUnliftIO m => Text -> (Bool -> m a) -> m a Source #

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.

withPopupModalOpen :: MonadUnliftIO m => Text -> m () -> m () Source #

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.

beginPopupModal :: MonadIO m => Text -> m Bool Source #

Returns True if the modal is open, and you can start outputting to it.

Wraps ImGui::BeginPopupModal()

Item context

itemContextPopup :: MonadUnliftIO m => m () -> m () Source #

Attach item context popup to right mouse button click on a last item.

withPopupContextItemOpen :: MonadUnliftIO m => Maybe Text -> ImGuiPopupFlags -> m () -> m () Source #

withPopupContextItem :: MonadUnliftIO m => Maybe Text -> ImGuiPopupFlags -> (Bool -> m a) -> m a Source #

Window context

windowContextPopup :: MonadUnliftIO m => m () -> m () Source #

Attach item context popup to right mouse button click on a current window.

withPopupContextWindowOpen :: MonadUnliftIO m => Maybe Text -> ImGuiPopupFlags -> m () -> m () Source #

withPopupContextWindow :: MonadUnliftIO m => Maybe Text -> ImGuiPopupFlags -> (Bool -> m a) -> m a Source #

Void context

voidContextPopup :: MonadUnliftIO m => m () -> m () Source #

Attach item context popup to right mouse button click outside of any windows.

withPopupContextVoidOpen :: MonadUnliftIO m => Maybe Text -> ImGuiPopupFlags -> m () -> m () Source #

withPopupContextVoid :: MonadUnliftIO m => Maybe Text -> ImGuiPopupFlags -> (Bool -> m a) -> m a Source #

Manual

openPopup :: MonadIO m => Text -> m () Source #

Call to mark popup as open (don't call every frame!).

Wraps ImGui::OpenPopup()

openPopupOnItemClick :: MonadIO m => Text -> ImGuiPopupFlags -> m () Source #

Opens a defined popup (i.e. defined with withPopup) on defined action.

Example:

openPopupOnItemClick "myPopup" ImGuiPopupFlags_MouseButtonRight

Wraps ImGui::OpenPopup()

closeCurrentPopup :: MonadIO m => m () Source #

Manually close the popup we have begin-ed into.

Wraps ImGui::ClosePopup()

Queries

isCurrentPopupOpen :: MonadIO m => Text -> m Bool Source #

Check if the popup is open at the current beginPopup level of the popup stack.

isAnyPopupOpen :: MonadIO m => Text -> m Bool Source #

Check if *any* popup is open at the current beginPopup level of the popup stack.

isAnyLevelPopupOpen :: MonadIO m => Text -> m Bool Source #

Check if *any* popup is open at any level of the popup stack.

Item/Widgets Utilities

isItemHovered :: MonadIO m => m Bool Source #

Is the last item hovered? (and usable, aka not blocked by a popup, etc.).

Wraps ImGui::IsItemHovered()

Utilities

ListClipper

withListClipper :: (ClipItems t a, MonadUnliftIO m) => Maybe Float -> t a -> (a -> m ()) -> m () Source #

Clips a large list of items

The requirements on a are that they are all of the same height.

class ClipItems t a where Source #

Containers usable with ListClipper.

Methods

itemCount :: t a -> Maybe Int Source #

clipItems :: Int -> Int -> t a -> t a Source #

stepItems :: Monad m => (a -> m ()) -> t a -> m () Source #

Instances

Instances details
(Ord a, Enum a, Num a) => ClipItems ClipRange a Source # 
Instance details

Defined in DearImGui

Methods

itemCount :: ClipRange a -> Maybe Int Source #

clipItems :: Int -> Int -> ClipRange a -> ClipRange a Source #

stepItems :: Monad m => (a -> m ()) -> ClipRange a -> m () Source #

ClipItems Vector a Source # 
Instance details

Defined in DearImGui

Methods

itemCount :: Vector a -> Maybe Int Source #

clipItems :: Int -> Int -> Vector a -> Vector a Source #

stepItems :: Monad m => (a -> m ()) -> Vector a -> m () Source #

Storable a => ClipItems Vector a Source # 
Instance details

Defined in DearImGui

Methods

itemCount :: Vector a -> Maybe Int Source #

clipItems :: Int -> Int -> Vector a -> Vector a Source #

stepItems :: Monad m => (a -> m ()) -> Vector a -> m () Source #

Unbox a => ClipItems Vector a Source # 
Instance details

Defined in DearImGui

Methods

itemCount :: Vector a -> Maybe Int Source #

clipItems :: Int -> Int -> Vector a -> Vector a Source #

stepItems :: Monad m => (a -> m ()) -> Vector a -> m () Source #

ClipItems [] a Source #

Unbounded stream of items.

Instance details

Defined in DearImGui

Methods

itemCount :: [a] -> Maybe Int Source #

clipItems :: Int -> Int -> [a] -> [a] Source #

stepItems :: Monad m => (a -> m ()) -> [a] -> m () Source #

data ClipRange a Source #

ClipList helper for arbitrary unmaterialized ranges.

Constructors

ClipRange a a 

Instances

Instances details
(Ord a, Enum a, Num a) => ClipItems ClipRange a Source # 
Instance details

Defined in DearImGui

Methods

itemCount :: ClipRange a -> Maybe Int Source #

clipItems :: Int -> Int -> ClipRange a -> ClipRange a Source #

stepItems :: Monad m => (a -> m ()) -> ClipRange a -> m () Source #

Show a => Show (ClipRange a) Source # 
Instance details

Defined in DearImGui

Eq a => Eq (ClipRange a) Source # 
Instance details

Defined in DearImGui

Methods

(==) :: ClipRange a -> ClipRange a -> Bool #

(/=) :: ClipRange a -> ClipRange a -> Bool #

Ord a => Ord (ClipRange a) Source # 
Instance details

Defined in DearImGui

Miscellaneous

getBackgroundDrawList :: MonadIO m => m DrawList Source #

This draw list will be the first rendering one.

Useful to quickly draw shapes/text behind dear imgui contents.

imCol32 :: CUChar -> CUChar -> CUChar -> CUChar -> ImU32 Source #

Generate 32-bit encoded colors using DearImgui macros.

Follows IMGUI_USE_BGRA_PACKED_COLOR define to put bytes in appropriate positions.

Types

class KnownNat (Count a) => FiniteEnum a where Source #

Minimal complete definition

Nothing

Associated Types

type Count a :: Nat Source #

Methods

count :: Natural Source #

Instances

Instances details
FiniteEnum ImGuiCol Source # 
Instance details

Defined in DearImGui.Enums

Associated Types

type Count ImGuiCol :: Nat Source #

Methods

count :: Natural Source #

FiniteEnum ImGuiDataType Source # 
Instance details

Defined in DearImGui.Enums

Associated Types

type Count ImGuiDataType :: Nat Source #

Methods

count :: Natural Source #

FiniteEnum ImGuiDir Source # 
Instance details

Defined in DearImGui.Enums

Associated Types

type Count ImGuiDir :: Nat Source #

Methods

count :: Natural Source #

FiniteEnum ImGuiKey Source # 
Instance details

Defined in DearImGui.Enums

Associated Types

type Count ImGuiKey :: Nat Source #

Methods

count :: Natural Source #

FiniteEnum ImGuiMouseButton Source # 
Instance details

Defined in DearImGui.Enums

Associated Types

type Count ImGuiMouseButton :: Nat Source #

Methods

count :: Natural Source #

FiniteEnum ImGuiMouseCursor Source # 
Instance details

Defined in DearImGui.Enums

Associated Types

type Count ImGuiMouseCursor :: Nat Source #

Methods

count :: Natural Source #

FiniteEnum ImGuiNavInput Source # 
Instance details

Defined in DearImGui.Enums

Associated Types

type Count ImGuiNavInput :: Nat Source #

Methods

count :: Natural Source #

FiniteEnum ImGuiStyleVar Source # 
Instance details

Defined in DearImGui.Enums

Associated Types

type Count ImGuiStyleVar :: Nat Source #

Methods

count :: Natural Source #

newtype ImGuiWindowFlags Source #

Flags: for Begin(), BeginChild()

Flags for ImGui::Begin()

Constructors

ImGuiWindowFlags CInt 

Instances

Instances details
Storable ImGuiWindowFlags Source # 
Instance details

Defined in DearImGui.Enums

Bits ImGuiWindowFlags Source # 
Instance details

Defined in DearImGui.Enums

Show ImGuiWindowFlags Source # 
Instance details

Defined in DearImGui.Enums

Eq ImGuiWindowFlags Source # 
Instance details

Defined in DearImGui.Enums

Ord ImGuiWindowFlags Source # 
Instance details

Defined in DearImGui.Enums

newtype ImGuiInputTextFlags Source #

Flags: for InputText(), InputTextMultiline()

Flags for ImGui::InputText()

Instances

Instances details
Storable ImGuiInputTextFlags Source # 
Instance details

Defined in DearImGui.Enums

Bits ImGuiInputTextFlags Source # 
Instance details

Defined in DearImGui.Enums

Show ImGuiInputTextFlags Source # 
Instance details

Defined in DearImGui.Enums

Eq ImGuiInputTextFlags Source # 
Instance details

Defined in DearImGui.Enums

Ord ImGuiInputTextFlags Source # 
Instance details

Defined in DearImGui.Enums

newtype ImGuiTreeNodeFlags Source #

Flags: for TreeNode(), TreeNodeEx(), CollapsingHeader()

Flags for ImGui::TreeNodeEx(), ImGui::CollapsingHeader*()

Constructors

ImGuiTreeNodeFlags CInt 

Instances

Instances details
Storable ImGuiTreeNodeFlags Source # 
Instance details

Defined in DearImGui.Enums

Bits ImGuiTreeNodeFlags Source # 
Instance details

Defined in DearImGui.Enums

Show ImGuiTreeNodeFlags Source # 
Instance details

Defined in DearImGui.Enums

Eq ImGuiTreeNodeFlags Source # 
Instance details

Defined in DearImGui.Enums

Ord ImGuiTreeNodeFlags Source # 
Instance details

Defined in DearImGui.Enums

newtype ImGuiPopupFlags Source #

Flags: for OpenPopup*(), BeginPopupContext*(), IsPopupOpen()

Flags for OpenPopup*(), BeginPopupContext*(), IsPopupOpen() functions. - To be backward compatible with older API which took an 'int mouse_button = 1' argument, we need to treat small flags values as a mouse button index, so we encode the mouse button in the first few bits of the flags. It is therefore guaranteed to be legal to pass a mouse button index in ImGuiPopupFlags. - For the same reason, we exceptionally default the ImGuiPopupFlags argument of BeginPopupContextXXX functions to 1 instead of 0. IMPORTANT: because the default parameter is 1 (==ImGuiPopupFlags_MouseButtonRight), if you rely on the default parameter and want to another another flag, you need to pass in the ImGuiPopupFlags_MouseButtonRight flag. - Multiple buttons currently cannot be combined/or-ed in those functions (we could allow it later).

Constructors

ImGuiPopupFlags CInt 

Instances

Instances details
Storable ImGuiPopupFlags Source # 
Instance details

Defined in DearImGui.Enums

Bits ImGuiPopupFlags Source # 
Instance details

Defined in DearImGui.Enums

Show ImGuiPopupFlags Source # 
Instance details

Defined in DearImGui.Enums

Eq ImGuiPopupFlags Source # 
Instance details

Defined in DearImGui.Enums

Ord ImGuiPopupFlags Source # 
Instance details

Defined in DearImGui.Enums

newtype ImGuiSelectableFlags Source #

Flags: for Selectable()

Flags for ImGui::Selectable()

Instances

Instances details
Storable ImGuiSelectableFlags Source # 
Instance details

Defined in DearImGui.Enums

Bits ImGuiSelectableFlags Source # 
Instance details

Defined in DearImGui.Enums

Show ImGuiSelectableFlags Source # 
Instance details

Defined in DearImGui.Enums

Eq ImGuiSelectableFlags Source # 
Instance details

Defined in DearImGui.Enums

Ord ImGuiSelectableFlags Source # 
Instance details

Defined in DearImGui.Enums

newtype ImGuiComboFlags Source #

Flags: for BeginCombo()

Flags for ImGui::BeginCombo()

Constructors

ImGuiComboFlags CInt 

Instances

Instances details
Storable ImGuiComboFlags Source # 
Instance details

Defined in DearImGui.Enums

Bits ImGuiComboFlags Source # 
Instance details

Defined in DearImGui.Enums

Show ImGuiComboFlags Source # 
Instance details

Defined in DearImGui.Enums

Eq ImGuiComboFlags Source # 
Instance details

Defined in DearImGui.Enums

Ord ImGuiComboFlags Source # 
Instance details

Defined in DearImGui.Enums

newtype ImGuiTabBarFlags Source #

Flags: for BeginTabBar()

Flags for ImGui::BeginTabBar()

Constructors

ImGuiTabBarFlags CInt 

Instances

Instances details
Storable ImGuiTabBarFlags Source # 
Instance details

Defined in DearImGui.Enums

Bits ImGuiTabBarFlags Source # 
Instance details

Defined in DearImGui.Enums

Show ImGuiTabBarFlags Source # 
Instance details

Defined in DearImGui.Enums

Eq ImGuiTabBarFlags Source # 
Instance details

Defined in DearImGui.Enums

Ord ImGuiTabBarFlags Source # 
Instance details

Defined in DearImGui.Enums

newtype ImGuiTabItemFlags Source #

Flags: for BeginTabItem()

Flags for ImGui::BeginTabItem()

Constructors

ImGuiTabItemFlags CInt 

Instances

Instances details
Storable ImGuiTabItemFlags Source # 
Instance details

Defined in DearImGui.Enums

Bits ImGuiTabItemFlags Source # 
Instance details

Defined in DearImGui.Enums

Show ImGuiTabItemFlags Source # 
Instance details

Defined in DearImGui.Enums

Eq ImGuiTabItemFlags Source # 
Instance details

Defined in DearImGui.Enums

Ord ImGuiTabItemFlags Source # 
Instance details

Defined in DearImGui.Enums

newtype ImGuiTableFlags Source #

Flags: For BeginTable()

Flags for ImGui::BeginTable() - Important! Sizing policies have complex and subtle side effects, much more so than you would expect. Read comments/demos carefully + experiment with live demos to get acquainted with them. - The DEFAULT sizing policies are: - Default to ImGuiTableFlags_SizingFixedFit if ScrollX is on, or if host window has ImGuiWindowFlags_AlwaysAutoResize. - Default to ImGuiTableFlags_SizingStretchSame if ScrollX is off. - When ScrollX is off: - Table defaults to ImGuiTableFlags_SizingStretchSame -> all Columns defaults to ImGuiTableColumnFlags_WidthStretch with same weight. - Columns sizing policy allowed: Stretch (default), Fixed/Auto. - Fixed Columns (if any) will generally obtain their requested width (unless the table cannot fit them all). - Stretch Columns will share the remaining width according to their respective weight. - Mixed Fixed/Stretch columns is possible but has various side-effects on resizing behaviors. The typical use of mixing sizing policies is: any number of LEADING Fixed columns, followed by one or two TRAILING Stretch columns. (this is because the visible order of columns have subtle but necessary effects on how they react to manual resizing). - When ScrollX is on: - Table defaults to ImGuiTableFlags_SizingFixedFit -> all Columns defaults to ImGuiTableColumnFlags_WidthFixed - Columns sizing policy allowed: Fixed/Auto mostly. - Fixed Columns can be enlarged as needed. Table will show an horizontal scrollbar if needed. - When using auto-resizing (non-resizable) fixed columns, querying the content width to use item right-alignment e.g. SetNextItemWidth(-FLT_MIN) doesn't make sense, would create a feedback loop. - Using Stretch columns OFTEN DOES NOT MAKE SENSE if ScrollX is on, UNLESS you have specified a value for inner_width in BeginTable(). If you specify a value for inner_width then effectively the scrolling space is known and Stretch or mixed Fixed/Stretch columns become meaningful again. - Read on documentation at the top of imgui_tables.cpp for details.

Constructors

ImGuiTableFlags CInt 

Instances

Instances details
Storable ImGuiTableFlags Source # 
Instance details

Defined in DearImGui.Enums

Bits ImGuiTableFlags Source # 
Instance details

Defined in DearImGui.Enums

Show ImGuiTableFlags Source # 
Instance details

Defined in DearImGui.Enums

Eq ImGuiTableFlags Source # 
Instance details

Defined in DearImGui.Enums

Ord ImGuiTableFlags Source # 
Instance details

Defined in DearImGui.Enums

newtype ImGuiTableColumnFlags Source #

Flags: For TableSetupColumn()

Flags for ImGui::TableSetupColumn()

Instances

Instances details
Storable ImGuiTableColumnFlags Source # 
Instance details

Defined in DearImGui.Enums

Bits ImGuiTableColumnFlags Source # 
Instance details

Defined in DearImGui.Enums

Show ImGuiTableColumnFlags Source # 
Instance details

Defined in DearImGui.Enums

Eq ImGuiTableColumnFlags Source # 
Instance details

Defined in DearImGui.Enums

Ord ImGuiTableColumnFlags Source # 
Instance details

Defined in DearImGui.Enums

newtype ImGuiTableRowFlags Source #

Flags: For TableNextRow()

Flags for ImGui::TableNextRow()

Constructors

ImGuiTableRowFlags CInt 

Instances

Instances details
Storable ImGuiTableRowFlags Source # 
Instance details

Defined in DearImGui.Enums

Bits ImGuiTableRowFlags Source # 
Instance details

Defined in DearImGui.Enums

Show ImGuiTableRowFlags Source # 
Instance details

Defined in DearImGui.Enums

Eq ImGuiTableRowFlags Source # 
Instance details

Defined in DearImGui.Enums

Ord ImGuiTableRowFlags Source # 
Instance details

Defined in DearImGui.Enums

newtype ImGuiTableBgTarget Source #

Enum: A color target for TableSetBgColor()

Enum for ImGui::TableSetBgColor() Background colors are rendering in 3 layers: - Layer 0: draw with RowBg0 color if set, otherwise draw with ColumnBg0 if set. - Layer 1: draw with RowBg1 color if set, otherwise draw with ColumnBg1 if set. - Layer 2: draw with CellBg color if set. The purpose of the two row/columns layers is to let you decide if a background color changes should override or blend with the existing color. When using ImGuiTableFlags_RowBg on the table, each row has the RowBg0 color automatically set for odd/even rows. If you set the color of RowBg0 target, your color will override the existing RowBg0 color. If you set the color of RowBg1 or ColumnBg1 target, your color will blend over the RowBg0 color.

Constructors

ImGuiTableBgTarget CInt 

Instances

Instances details
Storable ImGuiTableBgTarget Source # 
Instance details

Defined in DearImGui.Enums

Show ImGuiTableBgTarget Source # 
Instance details

Defined in DearImGui.Enums

Eq ImGuiTableBgTarget Source # 
Instance details

Defined in DearImGui.Enums

Ord ImGuiTableBgTarget Source # 
Instance details

Defined in DearImGui.Enums

newtype ImGuiFocusedFlags Source #

Flags: for IsWindowFocused()

Flags for ImGui::IsWindowFocused()

Constructors

ImGuiFocusedFlags CInt 

Instances

Instances details
Storable ImGuiFocusedFlags Source # 
Instance details

Defined in DearImGui.Enums

Bits ImGuiFocusedFlags Source # 
Instance details

Defined in DearImGui.Enums

Show ImGuiFocusedFlags Source # 
Instance details

Defined in DearImGui.Enums

Eq ImGuiFocusedFlags Source # 
Instance details

Defined in DearImGui.Enums

Ord ImGuiFocusedFlags Source # 
Instance details

Defined in DearImGui.Enums

newtype ImGuiHoveredFlags Source #

Flags: for IsItemHovered(), IsWindowHovered() etc.

Flags for ImGui::IsItemHovered(), ImGui::IsWindowHovered() Note: if you are trying to check whether your mouse should be dispatched to Dear ImGui or to your app, you should use 'io.WantCaptureMouse' instead! Please read the FAQ! Note: windows with the ImGuiWindowFlags_NoInputs flag are ignored by IsWindowHovered() calls.

Constructors

ImGuiHoveredFlags CInt 

Instances

Instances details
Storable ImGuiHoveredFlags Source # 
Instance details

Defined in DearImGui.Enums

Bits ImGuiHoveredFlags Source # 
Instance details

Defined in DearImGui.Enums

Show ImGuiHoveredFlags Source # 
Instance details

Defined in DearImGui.Enums

Eq ImGuiHoveredFlags Source # 
Instance details

Defined in DearImGui.Enums

Ord ImGuiHoveredFlags Source # 
Instance details

Defined in DearImGui.Enums

newtype ImGuiDragDropFlags Source #

Flags: for BeginDragDropSource(), AcceptDragDropPayload()

Flags for ImGui::BeginDragDropSource(), ImGui::AcceptDragDropPayload()

Constructors

ImGuiDragDropFlags CInt 

Instances

Instances details
Storable ImGuiDragDropFlags Source # 
Instance details

Defined in DearImGui.Enums

Bits ImGuiDragDropFlags Source # 
Instance details

Defined in DearImGui.Enums

Show ImGuiDragDropFlags Source # 
Instance details

Defined in DearImGui.Enums

Eq ImGuiDragDropFlags Source # 
Instance details

Defined in DearImGui.Enums

Ord ImGuiDragDropFlags Source # 
Instance details

Defined in DearImGui.Enums

newtype ImGuiDataType Source #

Enum: A primary data type

A primary data type

Constructors

ImGuiDataType CInt 

Instances

Instances details
Storable ImGuiDataType Source # 
Instance details

Defined in DearImGui.Enums

Show ImGuiDataType Source # 
Instance details

Defined in DearImGui.Enums

FiniteEnum ImGuiDataType Source # 
Instance details

Defined in DearImGui.Enums

Associated Types

type Count ImGuiDataType :: Nat Source #

Methods

count :: Natural Source #

Eq ImGuiDataType Source # 
Instance details

Defined in DearImGui.Enums

Ord ImGuiDataType Source # 
Instance details

Defined in DearImGui.Enums

type Count ImGuiDataType Source # 
Instance details

Defined in DearImGui.Enums

newtype ImGuiDir Source #

Enum: A cardinal direction

A cardinal direction

Constructors

ImGuiDir CInt 

Instances

Instances details
Storable ImGuiDir Source # 
Instance details

Defined in DearImGui.Enums

Show ImGuiDir Source # 
Instance details

Defined in DearImGui.Enums

FiniteEnum ImGuiDir Source # 
Instance details

Defined in DearImGui.Enums

Associated Types

type Count ImGuiDir :: Nat Source #

Methods

count :: Natural Source #

Eq ImGuiDir Source # 
Instance details

Defined in DearImGui.Enums

Ord ImGuiDir Source # 
Instance details

Defined in DearImGui.Enums

type Count ImGuiDir Source # 
Instance details

Defined in DearImGui.Enums

type Count ImGuiDir = 4

newtype ImGuiSortDirection Source #

Enum: A sorting direction (ascending or descending)

A sorting direction

Constructors

ImGuiSortDirection CInt 

Instances

Instances details
Storable ImGuiSortDirection Source # 
Instance details

Defined in DearImGui.Enums

Show ImGuiSortDirection Source # 
Instance details

Defined in DearImGui.Enums

Eq ImGuiSortDirection Source # 
Instance details

Defined in DearImGui.Enums

Ord ImGuiSortDirection Source # 
Instance details

Defined in DearImGui.Enums

newtype ImGuiKey Source #

Enum: A key identifier

Constructors

ImGuiKey CInt 

Instances

Instances details
Storable ImGuiKey Source # 
Instance details

Defined in DearImGui.Enums

Show ImGuiKey Source # 
Instance details

Defined in DearImGui.Enums

FiniteEnum ImGuiKey Source # 
Instance details

Defined in DearImGui.Enums

Associated Types

type Count ImGuiKey :: Nat Source #

Methods

count :: Natural Source #

Eq ImGuiKey Source # 
Instance details

Defined in DearImGui.Enums

Ord ImGuiKey Source # 
Instance details

Defined in DearImGui.Enums

type Count ImGuiKey Source # 
Instance details

Defined in DearImGui.Enums

type Count ImGuiKey = 648

newtype ImGuiKeyModFlags Source #

Flags: for io.KeyMods (CtrlShiftAlt/Super)

Helper "flags" version of key-mods to store and compare multiple key-mods easily. Sometimes used for storage (e.g. io.KeyMods) but otherwise not much used in public API.

Constructors

ImGuiKeyModFlags CInt 

Instances

Instances details
Storable ImGuiKeyModFlags Source # 
Instance details

Defined in DearImGui.Enums

Bits ImGuiKeyModFlags Source # 
Instance details

Defined in DearImGui.Enums

Show ImGuiKeyModFlags Source # 
Instance details

Defined in DearImGui.Enums

Eq ImGuiKeyModFlags Source # 
Instance details

Defined in DearImGui.Enums

Ord ImGuiKeyModFlags Source # 
Instance details

Defined in DearImGui.Enums

newtype ImGuiNavInput Source #

Enum: An input identifier for navigation

Gamepad/Keyboard navigation Keyboard: Set io.ConfigFlags |= ImGuiConfigFlags_NavEnableKeyboard to enable. NewFrame() will automatically fill io.NavInputs[] based on your io.AddKeyEvent() calls. Gamepad: Set io.ConfigFlags |= ImGuiConfigFlags_NavEnableGamepad to enable. Backend: set ImGuiBackendFlags_HasGamepad and fill the io.NavInputs[] fields before calling NewFrame(). Note that io.NavInputs[] is cleared by EndFrame(). Read instructions in imgui.cpp for more details. Download PNGPSD at http:dearimgui.orgcontrols_sheets.

Constructors

ImGuiNavInput CInt 

Instances

Instances details
Storable ImGuiNavInput Source # 
Instance details

Defined in DearImGui.Enums

Show ImGuiNavInput Source # 
Instance details

Defined in DearImGui.Enums

FiniteEnum ImGuiNavInput Source # 
Instance details

Defined in DearImGui.Enums

Associated Types

type Count ImGuiNavInput :: Nat Source #

Methods

count :: Natural Source #

Eq ImGuiNavInput Source # 
Instance details

Defined in DearImGui.Enums

Ord ImGuiNavInput Source # 
Instance details

Defined in DearImGui.Enums

type Count ImGuiNavInput Source # 
Instance details

Defined in DearImGui.Enums

newtype ImGuiConfigFlags Source #

Flags: for io.ConfigFlags

Configuration flags stored in io.ConfigFlags. Set by user/application.

Constructors

ImGuiConfigFlags CInt 

Instances

Instances details
Storable ImGuiConfigFlags Source # 
Instance details

Defined in DearImGui.Enums

Bits ImGuiConfigFlags Source # 
Instance details

Defined in DearImGui.Enums

Show ImGuiConfigFlags Source # 
Instance details

Defined in DearImGui.Enums

Eq ImGuiConfigFlags Source # 
Instance details

Defined in DearImGui.Enums

Ord ImGuiConfigFlags Source # 
Instance details

Defined in DearImGui.Enums

newtype ImGuiBackendFlags Source #

Flags: for io.BackendFlags

Backend capabilities flags stored in io.BackendFlags. Set by imgui_impl_xxx or custom backend.

Constructors

ImGuiBackendFlags CInt 

Instances

Instances details
Storable ImGuiBackendFlags Source # 
Instance details

Defined in DearImGui.Enums

Bits ImGuiBackendFlags Source # 
Instance details

Defined in DearImGui.Enums

Show ImGuiBackendFlags Source # 
Instance details

Defined in DearImGui.Enums

Eq ImGuiBackendFlags Source # 
Instance details

Defined in DearImGui.Enums

Ord ImGuiBackendFlags Source # 
Instance details

Defined in DearImGui.Enums

newtype ImGuiCol Source #

Enum: A color identifier for styling

Enumeration for PushStyleColor() / PopStyleColor()

Constructors

ImGuiCol CInt 

Instances

Instances details
Storable ImGuiCol Source # 
Instance details

Defined in DearImGui.Enums

Show ImGuiCol Source # 
Instance details

Defined in DearImGui.Enums

FiniteEnum ImGuiCol Source # 
Instance details

Defined in DearImGui.Enums

Associated Types

type Count ImGuiCol :: Nat Source #

Methods

count :: Natural Source #

Eq ImGuiCol Source # 
Instance details

Defined in DearImGui.Enums

Ord ImGuiCol Source # 
Instance details

Defined in DearImGui.Enums

type Count ImGuiCol Source # 
Instance details

Defined in DearImGui.Enums

type Count ImGuiCol = 53

newtype ImGuiStyleVar Source #

Enum: A variable identifier for styling

Enumeration for PushStyleVar() / PopStyleVar() to temporarily modify the ImGuiStyle structure. - The enum only refers to fields of ImGuiStyle which makes sense to be pushed/popped inside UI code. During initialization or between frames, feel free to just poke into ImGuiStyle directly. - Tip: Use your programming IDE navigation facilities on the names in the _second column_ below to find the actual members and their description. In Visual Studio IDE: CTRL+comma (Edit.NavigateTo) can follow symbols in comments, whereas CTRL+F12 (Edit.GoToImplementation) cannot. With Visual Assist installed: ALT+G (VAssistX.GoToImplementation) can also follow symbols in comments. - When changing this enum, you need to update the associated internal table GStyleVarInfo[] accordingly. This is where we link enum values to members offset/type.

Constructors

ImGuiStyleVar CInt 

Instances

Instances details
Storable ImGuiStyleVar Source # 
Instance details

Defined in DearImGui.Enums

Show ImGuiStyleVar Source # 
Instance details

Defined in DearImGui.Enums

FiniteEnum ImGuiStyleVar Source # 
Instance details

Defined in DearImGui.Enums

Associated Types

type Count ImGuiStyleVar :: Nat Source #

Methods

count :: Natural Source #

Eq ImGuiStyleVar Source # 
Instance details

Defined in DearImGui.Enums

Ord ImGuiStyleVar Source # 
Instance details

Defined in DearImGui.Enums

type Count ImGuiStyleVar Source # 
Instance details

Defined in DearImGui.Enums

newtype ImGuiButtonFlags Source #

Flags: for InvisibleButton()

Flags for InvisibleButton() [extended in imgui_internal.h]

Constructors

ImGuiButtonFlags CInt 

Instances

Instances details
Storable ImGuiButtonFlags Source # 
Instance details

Defined in DearImGui.Enums

Bits ImGuiButtonFlags Source # 
Instance details

Defined in DearImGui.Enums

Show ImGuiButtonFlags Source # 
Instance details

Defined in DearImGui.Enums

Eq ImGuiButtonFlags Source # 
Instance details

Defined in DearImGui.Enums

Ord ImGuiButtonFlags Source # 
Instance details

Defined in DearImGui.Enums

newtype ImGuiColorEditFlags Source #

Flags: for ColorEdit4(), ColorPicker4() etc.

Flags for ColorEdit3() ColorEdit4() ColorPicker3() ColorPicker4() ColorButton()

Instances

Instances details
Storable ImGuiColorEditFlags Source # 
Instance details

Defined in DearImGui.Enums

Bits ImGuiColorEditFlags Source # 
Instance details

Defined in DearImGui.Enums

Show ImGuiColorEditFlags Source # 
Instance details

Defined in DearImGui.Enums

Eq ImGuiColorEditFlags Source # 
Instance details

Defined in DearImGui.Enums

Ord ImGuiColorEditFlags Source # 
Instance details

Defined in DearImGui.Enums

newtype ImGuiSliderFlags Source #

Flags: for DragFloat(), DragInt(), SliderFloat(), SliderInt() etc.

Flags for DragFloat(), DragInt(), SliderFloat(), SliderInt() etc. We use the same sets of flags for DragXXX() and SliderXXX() functions as the features are the same and it makes it easier to swap them.

Constructors

ImGuiSliderFlags CInt 

Instances

Instances details
Storable ImGuiSliderFlags Source # 
Instance details

Defined in DearImGui.Enums

Bits ImGuiSliderFlags Source # 
Instance details

Defined in DearImGui.Enums

Show ImGuiSliderFlags Source # 
Instance details

Defined in DearImGui.Enums

Eq ImGuiSliderFlags Source # 
Instance details

Defined in DearImGui.Enums

Ord ImGuiSliderFlags Source # 
Instance details

Defined in DearImGui.Enums

newtype ImGuiMouseButton Source #

Enum: A mouse button identifier (0=left, 1=right, 2=middle)

Identify a mouse button. Those values are guaranteed to be stable and we frequently use 0/1 directly. Named enums provided for convenience.

Constructors

ImGuiMouseButton CInt 

Instances

Instances details
Storable ImGuiMouseButton Source # 
Instance details

Defined in DearImGui.Enums

Show ImGuiMouseButton Source # 
Instance details

Defined in DearImGui.Enums

FiniteEnum ImGuiMouseButton Source # 
Instance details

Defined in DearImGui.Enums

Associated Types

type Count ImGuiMouseButton :: Nat Source #

Methods

count :: Natural Source #

Eq ImGuiMouseButton Source # 
Instance details

Defined in DearImGui.Enums

Ord ImGuiMouseButton Source # 
Instance details

Defined in DearImGui.Enums

type Count ImGuiMouseButton Source # 
Instance details

Defined in DearImGui.Enums

newtype ImGuiMouseCursor Source #

Enum: A mouse cursor identifier

Enumeration for GetMouseCursor() User code may request backend to display given cursor by calling SetMouseCursor(), which is why we have some cursors that are marked unused here

Constructors

ImGuiMouseCursor CInt 

Instances

Instances details
Storable ImGuiMouseCursor Source # 
Instance details

Defined in DearImGui.Enums

Show ImGuiMouseCursor Source # 
Instance details

Defined in DearImGui.Enums

FiniteEnum ImGuiMouseCursor Source # 
Instance details

Defined in DearImGui.Enums

Associated Types

type Count ImGuiMouseCursor :: Nat Source #

Methods

count :: Natural Source #

Eq ImGuiMouseCursor Source # 
Instance details

Defined in DearImGui.Enums

Ord ImGuiMouseCursor Source # 
Instance details

Defined in DearImGui.Enums

type Count ImGuiMouseCursor Source # 
Instance details

Defined in DearImGui.Enums

newtype ImGuiCond Source #

Enum: A condition for many Set*() functions

Enumeration for ImGui::SetWindow***(), SetNextWindow***(), SetNextItem***() functions Represent a condition. Important: Treat as a regular enum! Do NOT combine multiple values using binary operators! All the functions above treat 0 as a shortcut to ImGuiCond_Always.

Constructors

ImGuiCond CInt 

newtype ImDrawFlags Source #

Flags: for ImDrawList functions

Flags for ImDrawList functions (Legacy: bit 0 must always correspond to ImDrawFlags_Closed to be backward compatible with old API using a bool. Bits 1..3 must be unused)

Constructors

ImDrawFlags CInt 

Instances

Instances details
Storable ImDrawFlags Source # 
Instance details

Defined in DearImGui.Enums

Bits ImDrawFlags Source # 
Instance details

Defined in DearImGui.Enums

Show ImDrawFlags Source # 
Instance details

Defined in DearImGui.Enums

Eq ImDrawFlags Source # 
Instance details

Defined in DearImGui.Enums

Ord ImDrawFlags Source # 
Instance details

Defined in DearImGui.Enums

newtype ImDrawListFlags Source #

Flags: for ImDrawList instance

Flags for ImDrawList instance. Those are set automatically by ImGui:: functions from ImGuiIO settings, and generally not manipulated directly. It is however possible to temporarily alter flags between calls to ImDrawList:: functions.

Constructors

ImDrawListFlags CInt 

Instances

Instances details
Storable ImDrawListFlags Source # 
Instance details

Defined in DearImGui.Enums

Bits ImDrawListFlags Source # 
Instance details

Defined in DearImGui.Enums

Show ImDrawListFlags Source # 
Instance details

Defined in DearImGui.Enums

Eq ImDrawListFlags Source # 
Instance details

Defined in DearImGui.Enums

Ord ImDrawListFlags Source # 
Instance details

Defined in DearImGui.Enums

newtype ImFontAtlasFlags Source #

Flags: for ImFontAtlas build

Flags for ImFontAtlas build

Constructors

ImFontAtlasFlags CInt 

Instances

Instances details
Storable ImFontAtlasFlags Source # 
Instance details

Defined in DearImGui.Enums

Bits ImFontAtlasFlags Source # 
Instance details

Defined in DearImGui.Enums

Show ImFontAtlasFlags Source # 
Instance details

Defined in DearImGui.Enums

Eq ImFontAtlasFlags Source # 
Instance details

Defined in DearImGui.Enums

Ord ImFontAtlasFlags Source # 
Instance details

Defined in DearImGui.Enums

pattern ImFontAtlasFlags_NoBakedLines :: ImFontAtlasFlags Source #

Don't build thick line textures into the atlas (save a little texture memory). The AntiAliasedLinesUseTex features uses them, otherwise they will be rendered using polygons (more expensive for CPU/GPU).

pattern ImFontAtlasFlags_NoMouseCursors :: ImFontAtlasFlags Source #

Don't build software mouse cursors into the atlas (save a little texture memory)

pattern ImFontAtlasFlags_NoPowerOfTwoHeight :: ImFontAtlasFlags Source #

Don't round the height to next power of two

pattern ImDrawListFlags_AllowVtxOffset :: ImDrawListFlags Source #

Can emit 'VtxOffset > 0' to allow large meshes. Set when ImGuiBackendFlags_RendererHasVtxOffset is enabled.

pattern ImDrawListFlags_AntiAliasedFill :: ImDrawListFlags Source #

Enable anti-aliased edge around filled shapes (rounded rectangles, circles).

pattern ImDrawListFlags_AntiAliasedLinesUseTex :: ImDrawListFlags Source #

Enable anti-aliased lines/borders using textures when possible. Require backend to render with bilinear filtering.

pattern ImDrawListFlags_AntiAliasedLines :: ImDrawListFlags Source #

Enable anti-aliased lines/borders (*2 the number of triangles for 1.0f wide line or lines thin enough to be drawn using textures, otherwise *3 the number of triangles)

pattern ImDrawFlags_RoundCornersDefault_ :: ImDrawFlags Source #

Default to ALL corners if none of the _RoundCornersXX flags are specified.

pattern ImDrawFlags_RoundCornersNone :: ImDrawFlags Source #

AddRect(), AddRectFilled(), PathRect(): disable rounding on all corners (when rounding > 0.0f). This is NOT zero, NOT an implicit flag!

pattern ImDrawFlags_RoundCornersBottomRight :: ImDrawFlags Source #

AddRect(), AddRectFilled(), PathRect(): enable rounding bottom-right corner only (when rounding > 0.0f, we default to all corners). Wax 0x08.

pattern ImDrawFlags_RoundCornersBottomLeft :: ImDrawFlags Source #

AddRect(), AddRectFilled(), PathRect(): enable rounding bottom-left corner only (when rounding > 0.0f, we default to all corners). Was 0x04.

pattern ImDrawFlags_RoundCornersTopRight :: ImDrawFlags Source #

AddRect(), AddRectFilled(), PathRect(): enable rounding top-right corner only (when rounding > 0.0f, we default to all corners). Was 0x02.

pattern ImDrawFlags_RoundCornersTopLeft :: ImDrawFlags Source #

AddRect(), AddRectFilled(), PathRect(): enable rounding top-left corner only (when rounding > 0.0f, we default to all corners). Was 0x01.

pattern ImDrawFlags_Closed :: ImDrawFlags Source #

PathStroke(), AddPolyline(): specify that shape should be closed (Important: this is always == 1 for legacy reason)

pattern ImGuiCond_Appearing :: ImGuiCond Source #

Set the variable if the objectwindow is appearing after being hiddeninactive (or the first time)

pattern ImGuiCond_FirstUseEver :: ImGuiCond Source #

Set the variable if the object/window has no persistently saved data (no entry in .ini file)

pattern ImGuiCond_Once :: ImGuiCond Source #

Set the variable once per runtime session (only the first call will succeed)

pattern ImGuiCond_Always :: ImGuiCond Source #

No condition (always set the variable)

pattern ImGuiCond_None :: ImGuiCond Source #

No condition (always set the variable), same as _Always

pattern ImGuiMouseCursor_NotAllowed :: ImGuiMouseCursor Source #

When hovering something with disallowed interaction. Usually a crossed circle.

pattern ImGuiMouseCursor_Hand :: ImGuiMouseCursor Source #

(Unused by Dear ImGui functions. Use for e.g. hyperlinks)

pattern ImGuiMouseCursor_ResizeNWSE :: ImGuiMouseCursor Source #

When hovering over the bottom-right corner of a window

pattern ImGuiMouseCursor_ResizeNESW :: ImGuiMouseCursor Source #

When hovering over the bottom-left corner of a window

pattern ImGuiMouseCursor_ResizeEW :: ImGuiMouseCursor Source #

When hovering over a vertical border or a column

pattern ImGuiMouseCursor_ResizeNS :: ImGuiMouseCursor Source #

When hovering over an horizontal border

pattern ImGuiMouseCursor_ResizeAll :: ImGuiMouseCursor Source #

(Unused by Dear ImGui functions)

pattern ImGuiMouseCursor_TextInput :: ImGuiMouseCursor Source #

When hovering over InputText, etc.

pattern ImGuiSliderFlags_InvalidMask_ :: ImGuiSliderFlags Source #

Internal
We treat using those bits as being potentially a 'float power' argument from the previous API that has got miscast to this enum, and will trigger an assert if needed.

pattern ImGuiSliderFlags_NoInput :: ImGuiSliderFlags Source #

Disable CTRL+Click or Enter key allowing to input text directly into the widget

pattern ImGuiSliderFlags_NoRoundToFormat :: ImGuiSliderFlags Source #

Disable rounding underlying value to match precision of the display format string (e.g. %.3f values are rounded to those 3 digits)

pattern ImGuiSliderFlags_Logarithmic :: ImGuiSliderFlags Source #

Make the widget logarithmic (linear otherwise). Consider using ImGuiSliderFlags_NoRoundToFormat with this if using a format-string with small amount of digits.

pattern ImGuiSliderFlags_AlwaysClamp :: ImGuiSliderFlags Source #

Clamp value to min/max bounds when input manually with CTRL+Click. By default CTRL+Click allows going out of bounds.

pattern ImGuiColorEditFlags_InputMask_ :: ImGuiColorEditFlags Source #

Obsolete names (will be removed)

pattern ImGuiColorEditFlags_InputHSV :: ImGuiColorEditFlags Source #

Input
// ColorEdit, ColorPicker: input and output data in HSV format.

pattern ImGuiColorEditFlags_InputRGB :: ImGuiColorEditFlags Source #

Input
// ColorEdit, ColorPicker: input and output data in RGB format.

pattern ImGuiColorEditFlags_PickerHueWheel :: ImGuiColorEditFlags Source #

Picker
/ ColorPicker: wheel for Hue, triangle for SatValue.

pattern ImGuiColorEditFlags_PickerHueBar :: ImGuiColorEditFlags Source #

Picker
/ ColorPicker: bar for Hue, rectangle for SatValue.

pattern ImGuiColorEditFlags_Float :: ImGuiColorEditFlags Source #

DataType
// ColorEdit, ColorPicker, ColorButton: _display_ values formatted as 0.0f..1.0f floats instead of 0..255 integers. No round-trip of value via integers.

pattern ImGuiColorEditFlags_Uint8 :: ImGuiColorEditFlags Source #

DataType
// ColorEdit, ColorPicker, ColorButton: _display_ values formatted as 0..255.

pattern ImGuiColorEditFlags_DisplayRGB :: ImGuiColorEditFlags Source #

Display
/ ColorEdit: override _display_ type among RGBHSVHex. ColorPicker: select any combination using one or more of RGBHSV/Hex.

pattern ImGuiColorEditFlags_HDR :: ImGuiColorEditFlags Source #

// (WIP) ColorEdit: Currently only disable 0.0f..1.0f limits in RGBA edition (note: you probably want to use ImGuiColorEditFlags_Float flag as well).

pattern ImGuiColorEditFlags_AlphaPreviewHalf :: ImGuiColorEditFlags Source #

/ ColorEdit, ColorPicker, ColorButton: display half opaque half checkerboard, instead of opaque.

pattern ImGuiColorEditFlags_AlphaPreview :: ImGuiColorEditFlags Source #

// ColorEdit, ColorPicker, ColorButton: display preview as a transparent color over a checkerboard, instead of opaque.

pattern ImGuiColorEditFlags_AlphaBar :: ImGuiColorEditFlags Source #

/ ColorEdit, ColorPicker: show vertical alpha bargradient in picker.

pattern ImGuiColorEditFlags_NoBorder :: ImGuiColorEditFlags Source #

// ColorButton: disable border (which is enforced by default)

pattern ImGuiColorEditFlags_NoDragDrop :: ImGuiColorEditFlags Source #

// ColorEdit: disable drag and drop target. ColorButton: disable drag and drop source.

pattern ImGuiColorEditFlags_NoSidePreview :: ImGuiColorEditFlags Source #

// ColorPicker: disable bigger color preview on right side of the picker, use small color square preview instead.

pattern ImGuiColorEditFlags_NoLabel :: ImGuiColorEditFlags Source #

// ColorEdit, ColorPicker: disable display of inline text label (the label is still forwarded to the tooltip and picker).

pattern ImGuiColorEditFlags_NoTooltip :: ImGuiColorEditFlags Source #

// ColorEdit, ColorPicker, ColorButton: disable tooltip when hovering the preview.

pattern ImGuiColorEditFlags_NoInputs :: ImGuiColorEditFlags Source #

/ ColorEdit, ColorPicker: disable inputs sliderstext widgets (e.g. to show only the small preview color square).

pattern ImGuiColorEditFlags_NoSmallPreview :: ImGuiColorEditFlags Source #

// ColorEdit, ColorPicker: disable color square preview next to the inputs. (e.g. to show only the inputs)

pattern ImGuiColorEditFlags_NoOptions :: ImGuiColorEditFlags Source #

/ ColorEdit: disable toggling options menu when right-clicking on inputssmall preview.

pattern ImGuiColorEditFlags_NoPicker :: ImGuiColorEditFlags Source #

// ColorEdit: disable picker when clicking on color square.

pattern ImGuiColorEditFlags_NoAlpha :: ImGuiColorEditFlags Source #

// ColorEdit, ColorPicker, ColorButton: ignore Alpha component (will only read 3 components from the input pointer).

pattern ImGuiButtonFlags_MouseButtonMiddle :: ImGuiButtonFlags Source #

React on center mouse button

pattern ImGuiButtonFlags_MouseButtonRight :: ImGuiButtonFlags Source #

React on right mouse button

pattern ImGuiButtonFlags_MouseButtonLeft :: ImGuiButtonFlags Source #

React on left mouse button (default)

pattern ImGuiStyleVar_SelectableTextAlign :: ImGuiStyleVar Source #

ImVec2 SelectableTextAlign

pattern ImGuiStyleVar_ButtonTextAlign :: ImGuiStyleVar Source #

ImVec2 ButtonTextAlign

pattern ImGuiStyleVar_TabRounding :: ImGuiStyleVar Source #

float TabRounding

pattern ImGuiStyleVar_GrabRounding :: ImGuiStyleVar Source #

float GrabRounding

pattern ImGuiStyleVar_GrabMinSize :: ImGuiStyleVar Source #

float GrabMinSize

pattern ImGuiStyleVar_ScrollbarRounding :: ImGuiStyleVar Source #

float ScrollbarRounding

pattern ImGuiStyleVar_ScrollbarSize :: ImGuiStyleVar Source #

float ScrollbarSize

pattern ImGuiStyleVar_CellPadding :: ImGuiStyleVar Source #

ImVec2 CellPadding

pattern ImGuiStyleVar_IndentSpacing :: ImGuiStyleVar Source #

float IndentSpacing

pattern ImGuiStyleVar_ItemInnerSpacing :: ImGuiStyleVar Source #

ImVec2 ItemInnerSpacing

pattern ImGuiStyleVar_ItemSpacing :: ImGuiStyleVar Source #

ImVec2 ItemSpacing

pattern ImGuiStyleVar_FrameBorderSize :: ImGuiStyleVar Source #

float FrameBorderSize

pattern ImGuiStyleVar_FrameRounding :: ImGuiStyleVar Source #

float FrameRounding

pattern ImGuiStyleVar_FramePadding :: ImGuiStyleVar Source #

ImVec2 FramePadding

pattern ImGuiStyleVar_PopupBorderSize :: ImGuiStyleVar Source #

float PopupBorderSize

pattern ImGuiStyleVar_PopupRounding :: ImGuiStyleVar Source #

float PopupRounding

pattern ImGuiStyleVar_ChildBorderSize :: ImGuiStyleVar Source #

float ChildBorderSize

pattern ImGuiStyleVar_ChildRounding :: ImGuiStyleVar Source #

float ChildRounding

pattern ImGuiStyleVar_WindowTitleAlign :: ImGuiStyleVar Source #

ImVec2 WindowTitleAlign

pattern ImGuiStyleVar_WindowMinSize :: ImGuiStyleVar Source #

ImVec2 WindowMinSize

pattern ImGuiStyleVar_WindowBorderSize :: ImGuiStyleVar Source #

float WindowBorderSize

pattern ImGuiStyleVar_WindowRounding :: ImGuiStyleVar Source #

float WindowRounding

pattern ImGuiStyleVar_WindowPadding :: ImGuiStyleVar Source #

ImVec2 WindowPadding

pattern ImGuiStyleVar_DisabledAlpha :: ImGuiStyleVar Source #

float DisabledAlpha

pattern ImGuiCol_ModalWindowDimBg :: ImGuiCol Source #

Darken/colorize entire screen behind a modal window, when one is active

pattern ImGuiCol_NavWindowingDimBg :: ImGuiCol Source #

Darken/colorize entire screen behind the CTRL+TAB window list, when active

pattern ImGuiCol_NavWindowingHighlight :: ImGuiCol Source #

Highlight window when using CTRL+TAB

pattern ImGuiCol_NavHighlight :: ImGuiCol Source #

Gamepad/keyboard: current highlighted item

pattern ImGuiCol_TableRowBgAlt :: ImGuiCol Source #

Table row background (odd rows)

pattern ImGuiCol_TableRowBg :: ImGuiCol Source #

Table row background (even rows)

pattern ImGuiCol_TableBorderLight :: ImGuiCol Source #

Table inner borders (prefer using Alpha=1.0 here)

pattern ImGuiCol_TableBorderStrong :: ImGuiCol Source #

Table outer and header borders (prefer using Alpha=1.0 here)

pattern ImGuiCol_TableHeaderBg :: ImGuiCol Source #

Table header background

pattern ImGuiCol_Header :: ImGuiCol Source #

Header* colors are used for CollapsingHeader, TreeNode, Selectable, MenuItem

pattern ImGuiCol_FrameBg :: ImGuiCol Source #

Background of checkbox, radio button, plot, slider, text input

pattern ImGuiCol_PopupBg :: ImGuiCol Source #

Background of popups, menus, tooltips windows

pattern ImGuiCol_ChildBg :: ImGuiCol Source #

Background of child windows

pattern ImGuiCol_WindowBg :: ImGuiCol Source #

Background of normal windows

pattern ImGuiBackendFlags_RendererHasVtxOffset :: ImGuiBackendFlags Source #

Backend Renderer supports ImDrawCmd::VtxOffset. This enables output of large meshes (64K+ vertices) while still using 16-bit indices.

pattern ImGuiBackendFlags_HasSetMousePos :: ImGuiBackendFlags Source #

Backend Platform supports io.WantSetMousePos requests to reposition the OS mouse position (only used if ImGuiConfigFlags_NavEnableSetMousePos is set).

pattern ImGuiBackendFlags_HasMouseCursors :: ImGuiBackendFlags Source #

Backend Platform supports honoring GetMouseCursor() value to change the OS cursor shape.

pattern ImGuiBackendFlags_HasGamepad :: ImGuiBackendFlags Source #

Backend Platform supports gamepad and currently has one connected.

pattern ImGuiConfigFlags_IsTouchScreen :: ImGuiConfigFlags Source #

Application is using a touch screen instead of a mouse.

pattern ImGuiConfigFlags_IsSRGB :: ImGuiConfigFlags Source #

Application is SRGB-aware.

pattern ImGuiConfigFlags_NoMouseCursorChange :: ImGuiConfigFlags Source #

Instruct backend to not alter mouse cursor shape and visibility. Use if the backend cursor changes are interfering with yours and you don't want to use SetMouseCursor() to change mouse cursor. You may want to honor requests from imgui by reading GetMouseCursor() yourself instead.

pattern ImGuiConfigFlags_NoMouse :: ImGuiConfigFlags Source #

Instruct imgui to clear mouse position/buttons in NewFrame(). This allows ignoring the mouse information set by the backend.

pattern ImGuiConfigFlags_NavNoCaptureKeyboard :: ImGuiConfigFlags Source #

Instruct navigation to not set the io.WantCaptureKeyboard flag when io.NavActive is set.

pattern ImGuiConfigFlags_NavEnableSetMousePos :: ImGuiConfigFlags Source #

Instruct navigation to move the mouse cursor. May be useful on TV/console systems where moving a virtual mouse is awkward. Will update io.MousePos and set io.WantSetMousePos=true. If enabled you MUST honor io.WantSetMousePos requests in your backend, otherwise ImGui will react as if the mouse is jumping around back and forth.

pattern ImGuiConfigFlags_NavEnableGamepad :: ImGuiConfigFlags Source #

Master gamepad navigation enable flag. This is mostly to instruct your imgui backend to fill io.NavInputs[]. Backend also needs to set ImGuiBackendFlags_HasGamepad.

pattern ImGuiConfigFlags_NavEnableKeyboard :: ImGuiConfigFlags Source #

Master keyboard navigation enable flag. NewFrame() will automatically fill io.NavInputs[] based on io.AddKeyEvent() calls

pattern ImGuiNavInput_KeyLeft_ :: ImGuiNavInput Source #

Move left // = Arrow keys

pattern ImGuiNavInput_TweakFast :: ImGuiNavInput Source #

Faster tweaks // e.g. R1 or R2 (PS4), RB or RT (Xbox), R or ZL (Switch)

pattern ImGuiNavInput_TweakSlow :: ImGuiNavInput Source #

Slower tweaks // e.g. L1 or L2 (PS4), LB or LT (Xbox), L or ZL (Switch)

pattern ImGuiNavInput_FocusNext :: ImGuiNavInput Source #

Focus Prev window (w PadMenu) / e.g. R1 or R2 (PS4), RB or RT (Xbox), R or ZL (Switch)

pattern ImGuiNavInput_FocusPrev :: ImGuiNavInput Source #

Focus Next window (w PadMenu) / e.g. L1 or L2 (PS4), LB or LT (Xbox), L or ZL (Switch)

pattern ImGuiNavInput_LStickLeft :: ImGuiNavInput Source #

Scroll Move window (w PadMenu) / e.g. Left Analog Stick LeftRightUpDown

pattern ImGuiNavInput_DpadLeft :: ImGuiNavInput Source #

Move Tweak Resize window (w PadMenu) e.g. D-pad LeftRightUpDown (Gamepads), Arrow keys (Keyboard)

pattern ImGuiNavInput_Menu :: ImGuiNavInput Source #

Tap: Toggle menu Hold: Focus, Move, Resize / e.g. Square (PS4), X (Xbox), Y (Switch), Alt (Keyboard)

pattern ImGuiNavInput_Input :: ImGuiNavInput Source #

Text input On-Screen keyboard / e.g. Triang.(PS4), Y (Xbox), X (Switch), Return (Keyboard)

pattern ImGuiNavInput_Cancel :: ImGuiNavInput Source #

Cancel Close Exit // e.g. Circle (PS4), B (Xbox), B (Switch), Escape (Keyboard)

pattern ImGuiNavInput_Activate :: ImGuiNavInput Source #

Activate Open Toggle Tweak value / e.g. Cross (PS4), A (Xbox), A (Switch), Space (Keyboard)

pattern ImGuiKeyModFlags_Super :: ImGuiKeyModFlags Source #

CmdSuperWindows key

pattern ImGuiKey_GamepadLStickRight :: ImGuiKey Source #

Analog
// -> ImGuiNavInput_LStickRight

pattern ImGuiKey_GamepadLStickLeft :: ImGuiKey Source #

Analog
// -> ImGuiNavInput_LStickLeft

pattern ImGuiKey_GamepadLStickDown :: ImGuiKey Source #

Analog
// -> ImGuiNavInput_LStickDown

pattern ImGuiKey_GamepadLStickUp :: ImGuiKey Source #

Analog
// -> ImGuiNavInput_LStickUp

pattern ImGuiKey_GamepadR3 :: ImGuiKey Source #

R Thumbstick (Xbox) R3 (Switch) R3 (PS)

pattern ImGuiKey_GamepadL3 :: ImGuiKey Source #

L Thumbstick (Xbox) L3 (Switch) L3 (PS)

pattern ImGuiKey_GamepadR2 :: ImGuiKey Source #

R Trigger (Xbox) ZR (Switch) R2 (PS) [Analog]

pattern ImGuiKey_GamepadL2 :: ImGuiKey Source #

L Trigger (Xbox) ZL (Switch) L2 (PS) [Analog]

pattern ImGuiKey_GamepadR1 :: ImGuiKey Source #

R Bumper (Xbox) R (Switch) R1 (PS) // -> ImGuiNavInput_FocusNext + ImGuiNavInput_TweakFast

pattern ImGuiKey_GamepadL1 :: ImGuiKey Source #

L Bumper (Xbox) L (Switch) L1 (PS) // -> ImGuiNavInput_FocusPrev + ImGuiNavInput_TweakSlow

pattern ImGuiKey_GamepadDpadRight :: ImGuiKey Source #

D-pad Right // -> ImGuiNavInput_DpadRight

pattern ImGuiKey_GamepadDpadLeft :: ImGuiKey Source #

D-pad Left // -> ImGuiNavInput_DpadLeft

pattern ImGuiKey_GamepadDpadDown :: ImGuiKey Source #

D-pad Down // -> ImGuiNavInput_DpadDown

pattern ImGuiKey_GamepadDpadUp :: ImGuiKey Source #

D-pad Up // -> ImGuiNavInput_DpadUp

pattern ImGuiKey_GamepadFaceRight :: ImGuiKey Source #

B (Xbox) A (Switch) Circle (PS) // -> ImGuiNavInput_Cancel

pattern ImGuiKey_GamepadFaceLeft :: ImGuiKey Source #

X (Xbox) Y (Switch) Square (PS) // -> ImGuiNavInput_Menu

pattern ImGuiKey_GamepadFaceDown :: ImGuiKey Source #

A (Xbox) B (Switch) Cross (PS) // -> ImGuiNavInput_Activate

pattern ImGuiKey_GamepadFaceUp :: ImGuiKey Source #

Y (Xbox) X (Switch) Triangle (PS) // -> ImGuiNavInput_Input

pattern ImGuiKey_GamepadBack :: ImGuiKey Source #

View (Xbox) - (Switch) Share (PS) // --

pattern ImGuiKey_GamepadStart :: ImGuiKey Source #

Menu (Xbox) + (Switch) StartOptions (PS) / --

pattern ImGuiKey_KeypadEqual :: ImGuiKey Source #

Gamepad (some of those are analog values, 0.0f to 1.0f) // NAVIGATION action

pattern ImGuiKey_Backslash :: ImGuiKey Source #

(this text inhibit multiline comment caused by backslash)

pattern ImGuiKey_Tab :: ImGuiKey Source #

ImGuiKey_NamedKey_BEGIN

pattern ImGuiSortDirection_Descending :: ImGuiSortDirection Source #

Descending = 9->0, Z->A etc.

pattern ImGuiSortDirection_Ascending :: ImGuiSortDirection Source #

Ascending = 0->9, A->Z etc.

pattern ImGuiDataType_U64 :: ImGuiDataType Source #

unsigned long long / unsigned __int64

pattern ImGuiDataType_S64 :: ImGuiDataType Source #

long long / __int64

pattern ImGuiDataType_U32 :: ImGuiDataType Source #

unsigned int

pattern ImGuiDataType_U16 :: ImGuiDataType Source #

unsigned short

pattern ImGuiDataType_U8 :: ImGuiDataType Source #

unsigned char

pattern ImGuiDataType_S8 :: ImGuiDataType Source #

signed char / char (with sensible compilers)

pattern ImGuiDragDropFlags_AcceptPeekOnly :: ImGuiDragDropFlags Source #

For peeking ahead and inspecting the payload before delivery.

pattern ImGuiDragDropFlags_AcceptNoPreviewTooltip :: ImGuiDragDropFlags Source #

Request hiding the BeginDragDropSource tooltip from the BeginDragDropTarget site.

pattern ImGuiDragDropFlags_AcceptNoDrawDefaultRect :: ImGuiDragDropFlags Source #

Do not draw the default highlight rectangle when hovering over target.

pattern ImGuiDragDropFlags_AcceptBeforeDelivery :: ImGuiDragDropFlags Source #

AcceptDragDropPayload() will returns true even before the mouse button is released. You can then call IsDelivery() to test if the payload needs to be delivered.

pattern ImGuiDragDropFlags_SourceAutoExpirePayload :: ImGuiDragDropFlags Source #

Automatically expire the payload if the source cease to be submitted (otherwise payloads are persisting while being dragged)

pattern ImGuiDragDropFlags_SourceExtern :: ImGuiDragDropFlags Source #

External source (from outside of dear imgui), won't attempt to read current item/window info. Will always return true. Only one Extern source can be active simultaneously.

pattern ImGuiDragDropFlags_SourceAllowNullID :: ImGuiDragDropFlags Source #

Allow items such as Text(), Image() that have no unique identifier to be used as drag source, by manufacturing a temporary identifier based on their window-relative position. This is extremely unusual within the dear imgui ecosystem and so we made it explicit.

pattern ImGuiDragDropFlags_SourceNoHoldToOpenOthers :: ImGuiDragDropFlags Source #

Disable the behavior that allows to open tree nodes and collapsing header by holding over them while dragging a source item.

pattern ImGuiDragDropFlags_SourceNoDisableHover :: ImGuiDragDropFlags Source #

By default, when dragging we clear data so that IsItemHovered() will return false, to avoid subsequent user code submitting tooltips. This flag disable this behavior so you can still call IsItemHovered() on the source item.

pattern ImGuiDragDropFlags_SourceNoPreviewTooltip :: ImGuiDragDropFlags Source #

By default, a successful call to BeginDragDropSource opens a tooltip so you can display a preview or description of the source contents. This flag disable this behavior.

pattern ImGuiDragDropFlags_None :: ImGuiDragDropFlags Source #

BeginDragDropSource() flags

pattern ImGuiHoveredFlags_AllowWhenDisabled :: ImGuiHoveredFlags Source #

IsItemHovered() only: Return true even if the item is disabled

pattern ImGuiHoveredFlags_AllowWhenOverlapped :: ImGuiHoveredFlags Source #

IsItemHovered() only: Return true even if the position is obstructed or overlapped by another window

pattern ImGuiHoveredFlags_AllowWhenBlockedByActiveItem :: ImGuiHoveredFlags Source #

Return true even if an active item is blocking access to this item/window. Useful for Drag and Drop patterns.

pattern ImGuiHoveredFlags_AllowWhenBlockedByPopup :: ImGuiHoveredFlags Source #

Return true even if a popup window is normally blocking access to this item/window

pattern ImGuiHoveredFlags_NoPopupHierarchy :: ImGuiHoveredFlags Source #

IsWindowHovered() only: Do not consider popup hierarchy (do not treat popup emitter as parent of popup) (when used with _ChildWindows or _RootWindow)

pattern ImGuiHoveredFlags_AnyWindow :: ImGuiHoveredFlags Source #

IsWindowHovered() only: Return true if any window is hovered

pattern ImGuiHoveredFlags_RootWindow :: ImGuiHoveredFlags Source #

IsWindowHovered() only: Test from root window (top most parent of the current hierarchy)

pattern ImGuiHoveredFlags_ChildWindows :: ImGuiHoveredFlags Source #

IsWindowHovered() only: Return true if any children of the window is hovered

pattern ImGuiHoveredFlags_None :: ImGuiHoveredFlags Source #

Return true if directly over the item/window, not obstructed by another window, not obstructed by an active popup or modal blocking inputs under them.

pattern ImGuiFocusedFlags_NoPopupHierarchy :: ImGuiFocusedFlags Source #

Do not consider popup hierarchy (do not treat popup emitter as parent of popup) (when used with _ChildWindows or _RootWindow)

pattern ImGuiFocusedFlags_AnyWindow :: ImGuiFocusedFlags Source #

Return true if any window is focused. Important: If you are trying to tell how to dispatch your low-level inputs, do NOT use this. Use 'io.WantCaptureMouse' instead! Please read the FAQ!

pattern ImGuiFocusedFlags_RootWindow :: ImGuiFocusedFlags Source #

Test from root window (top most parent of the current hierarchy)

pattern ImGuiFocusedFlags_ChildWindows :: ImGuiFocusedFlags Source #

Return true if any children of the window is focused

pattern ImGuiTableBgTarget_CellBg :: ImGuiTableBgTarget Source #

Set cell background color (top-most color)

pattern ImGuiTableBgTarget_RowBg1 :: ImGuiTableBgTarget Source #

Set row background color 1 (generally used for selection marking)

pattern ImGuiTableBgTarget_RowBg0 :: ImGuiTableBgTarget Source #

Set row background color 0 (generally used for background, automatically set when ImGuiTableFlags_RowBg is used)

pattern ImGuiTableRowFlags_Headers :: ImGuiTableRowFlags Source #

Identify header row (set default background color + width of its contents accounted differently for auto column width)

pattern ImGuiTableColumnFlags_NoDirectResize_ :: ImGuiTableColumnFlags Source #

Internal
Disable user resizing this column directly (it may however we resized indirectly from its left edge)

pattern ImGuiTableColumnFlags_IsHovered :: ImGuiTableColumnFlags Source #

Status: is hovered by mouse

pattern ImGuiTableColumnFlags_IsSorted :: ImGuiTableColumnFlags Source #

Status: is currently part of the sort specs

pattern ImGuiTableColumnFlags_IsVisible :: ImGuiTableColumnFlags Source #

Status: is visible == is enabled AND not clipped by scrolling.

pattern ImGuiTableColumnFlags_IsEnabled :: ImGuiTableColumnFlags Source #

Status: is enabled == not hidden by user/api (referred to as Hide in _DefaultHide and _NoHide) flags.

pattern ImGuiTableColumnFlags_IndentDisable :: ImGuiTableColumnFlags Source #

Ignore current Indent value when entering cell (default for columns > 0). Indentation changes _within_ the cell will still be honored.

pattern ImGuiTableColumnFlags_IndentEnable :: ImGuiTableColumnFlags Source #

Use current Indent value when entering cell (default for column 0).

pattern ImGuiTableColumnFlags_PreferSortDescending :: ImGuiTableColumnFlags Source #

Make the initial sort direction Descending when first sorting on this column.

pattern ImGuiTableColumnFlags_PreferSortAscending :: ImGuiTableColumnFlags Source #

Make the initial sort direction Ascending when first sorting on this column (default).

pattern ImGuiTableColumnFlags_NoHeaderWidth :: ImGuiTableColumnFlags Source #

Disable header text width contribution to automatic column width.

pattern ImGuiTableColumnFlags_NoHeaderLabel :: ImGuiTableColumnFlags Source #

TableHeadersRow() will not submit label for this column. Convenient for some small columns. Name will still appear in context menu.

pattern ImGuiTableColumnFlags_NoSortDescending :: ImGuiTableColumnFlags Source #

Disable ability to sort in the descending direction.

pattern ImGuiTableColumnFlags_NoSortAscending :: ImGuiTableColumnFlags Source #

Disable ability to sort in the ascending direction.

pattern ImGuiTableColumnFlags_NoSort :: ImGuiTableColumnFlags Source #

Disable ability to sort on this field (even if ImGuiTableFlags_Sortable is set on the table).

pattern ImGuiTableColumnFlags_NoClip :: ImGuiTableColumnFlags Source #

Disable clipping for this column (all NoClip columns will render in a same draw command).

pattern ImGuiTableColumnFlags_NoHide :: ImGuiTableColumnFlags Source #

Disable ability to hide/disable this column.

pattern ImGuiTableColumnFlags_NoReorder :: ImGuiTableColumnFlags Source #

Disable manual reordering this column, this will also prevent other columns from crossing over this column.

pattern ImGuiTableColumnFlags_WidthFixed :: ImGuiTableColumnFlags Source #

Column will not stretch. Preferable with horizontal scrolling enabled (default if table sizing policy is _SizingFixedFit and table is resizable).

pattern ImGuiTableColumnFlags_WidthStretch :: ImGuiTableColumnFlags Source #

Column will stretch. Preferable with horizontal scrolling disabled (default if table sizing policy is _SizingStretchSame or _SizingStretchProp).

pattern ImGuiTableColumnFlags_DefaultSort :: ImGuiTableColumnFlags Source #

Default as a sorting column.

pattern ImGuiTableColumnFlags_DefaultHide :: ImGuiTableColumnFlags Source #

Default as a hidden/disabled column.

pattern ImGuiTableColumnFlags_Disabled :: ImGuiTableColumnFlags Source #

Overriding/master disable flag: hide column, won't show in context menu (unlike calling TableSetColumnEnabled() which manipulates the user accessible state)

pattern ImGuiTableFlags_SizingMask_ :: ImGuiTableFlags Source #

Obsolete names (will be removed soon)

pattern ImGuiTableFlags_SortTristate :: ImGuiTableFlags Source #

Allow no sorting, disable default sorting. TableGetSortSpecs() may return specs where (SpecsCount == 0).

pattern ImGuiTableFlags_SortMulti :: ImGuiTableFlags Source #

Hold shift when clicking headers to sort on multiple column. TableGetSortSpecs() may return specs where (SpecsCount > 1).

pattern ImGuiTableFlags_ScrollY :: ImGuiTableFlags Source #

Enable vertical scrolling. Require outer_size parameter of BeginTable() to specify the container size.

pattern ImGuiTableFlags_ScrollX :: ImGuiTableFlags Source #

Enable horizontal scrolling. Require outer_size parameter of BeginTable() to specify the container size. Changes default sizing policy. Because this create a child window, ScrollY is currently generally recommended when using ScrollX.

pattern ImGuiTableFlags_NoPadInnerX :: ImGuiTableFlags Source #

Disable inner padding between columns (double inner padding if BordersOuterV is on, single inner padding if BordersOuterV is off).

pattern ImGuiTableFlags_NoPadOuterX :: ImGuiTableFlags Source #

Default if BordersOuterV is off. Disable outer-most padding.

pattern ImGuiTableFlags_PadOuterX :: ImGuiTableFlags Source #

Default if BordersOuterV is on. Enable outer-most padding. Generally desirable if you have headers.

pattern ImGuiTableFlags_NoClip :: ImGuiTableFlags Source #

Disable clipping rectangle for every individual columns (reduce draw command count, items will be able to overflow into other columns). Generally incompatible with TableSetupScrollFreeze().

pattern ImGuiTableFlags_PreciseWidths :: ImGuiTableFlags Source #

Disable distributing remainder width to stretched columns (width allocation on a 100-wide table with 3 columns: Without this flag: 33,33,34. With this flag: 33,33,33). With larger number of columns, resizing will appear to be less smooth.

pattern ImGuiTableFlags_NoKeepColumnsVisible :: ImGuiTableFlags Source #

Disable keeping column always minimally visible when ScrollX is off and table gets too small. Not recommended if columns are resizable.

pattern ImGuiTableFlags_NoHostExtendY :: ImGuiTableFlags Source #

Make outer height stop exactly at outer_size.y (prevent auto-extending table past the limit). Only available when ScrollX/ScrollY are disabled. Data below the limit will be clipped and not visible.

pattern ImGuiTableFlags_NoHostExtendX :: ImGuiTableFlags Source #

Make outer width auto-fit to columns, overriding outer_size.x value. Only available when ScrollX/ScrollY are disabled and Stretch columns are not used.

pattern ImGuiTableFlags_SizingStretchSame :: ImGuiTableFlags Source #

Columns default to _WidthStretch with default weights all equal, unless overridden by TableSetupColumn().

pattern ImGuiTableFlags_SizingStretchProp :: ImGuiTableFlags Source #

Columns default to _WidthStretch with default weights proportional to each columns contents widths.

pattern ImGuiTableFlags_SizingFixedSame :: ImGuiTableFlags Source #

Columns default to _WidthFixed or _WidthAuto (if resizable or not resizable), matching the maximum contents width of all columns. Implicitly enable ImGuiTableFlags_NoKeepColumnsVisible.

pattern ImGuiTableFlags_SizingFixedFit :: ImGuiTableFlags Source #

Columns default to _WidthFixed or _WidthAuto (if resizable or not resizable), matching contents width.

pattern ImGuiTableFlags_NoBordersInBodyUntilResize :: ImGuiTableFlags Source #

ALPHA
Disable vertical borders in columns Body until hovered for resize (borders will always appears in Headers). -> May move to style

pattern ImGuiTableFlags_NoBordersInBody :: ImGuiTableFlags Source #

ALPHA
Disable vertical borders in columns Body (borders will always appears in Headers). -> May move to style

pattern ImGuiTableFlags_Borders :: ImGuiTableFlags Source #

Draw all borders.

pattern ImGuiTableFlags_BordersV :: ImGuiTableFlags Source #

Draw vertical borders.

pattern ImGuiTableFlags_BordersH :: ImGuiTableFlags Source #

Draw horizontal borders.

pattern ImGuiTableFlags_BordersOuterV :: ImGuiTableFlags Source #

Draw vertical borders on the left and right sides.

pattern ImGuiTableFlags_BordersInnerV :: ImGuiTableFlags Source #

Draw vertical borders between columns.

pattern ImGuiTableFlags_BordersOuterH :: ImGuiTableFlags Source #

Draw horizontal borders at the top and bottom.

pattern ImGuiTableFlags_BordersInnerH :: ImGuiTableFlags Source #

Draw horizontal borders between rows.

pattern ImGuiTableFlags_RowBg :: ImGuiTableFlags Source #

Set each RowBg color with ImGuiCol_TableRowBg or ImGuiCol_TableRowBgAlt (equivalent of calling TableSetBgColor with ImGuiTableBgFlags_RowBg0 on each row manually)

pattern ImGuiTableFlags_ContextMenuInBody :: ImGuiTableFlags Source #

Right-click on columns body/contents will display table context menu. By default it is available in TableHeadersRow().

pattern ImGuiTableFlags_NoSavedSettings :: ImGuiTableFlags Source #

Disable persisting columns order, width and sort settings in the .ini file.

pattern ImGuiTableFlags_Sortable :: ImGuiTableFlags Source #

Enable sorting. Call TableGetSortSpecs() to obtain sort specs. Also see ImGuiTableFlags_SortMulti and ImGuiTableFlags_SortTristate.

pattern ImGuiTableFlags_Hideable :: ImGuiTableFlags Source #

Enable hiding/disabling columns in context menu.

pattern ImGuiTableFlags_Reorderable :: ImGuiTableFlags Source #

Enable reordering columns in header row (need calling TableSetupColumn() + TableHeadersRow() to display headers)

pattern ImGuiTableFlags_Resizable :: ImGuiTableFlags Source #

Enable resizing columns.

pattern ImGuiTabItemFlags_Trailing :: ImGuiTabItemFlags Source #

Enforce the tab position to the right of the tab bar (before the scrolling buttons)

pattern ImGuiTabItemFlags_Leading :: ImGuiTabItemFlags Source #

Enforce the tab position to the left of the tab bar (after the tab list popup button)

pattern ImGuiTabItemFlags_NoReorder :: ImGuiTabItemFlags Source #

Disable reordering this tab or having another tab cross over this tab

pattern ImGuiTabItemFlags_NoTooltip :: ImGuiTabItemFlags Source #

Disable tooltip for the given tab

pattern ImGuiTabItemFlags_NoPushId :: ImGuiTabItemFlags Source #

Don't call PushID(tab->ID)PopID() on BeginTabItem()EndTabItem()

pattern ImGuiTabItemFlags_NoCloseWithMiddleMouseButton :: ImGuiTabItemFlags Source #

Disable behavior of closing tabs (that are submitted with p_open != NULL) with middle mouse button. You can still repro this behavior on user's side with if (IsItemHovered() && IsMouseClicked(2)) *p_open = false.

pattern ImGuiTabItemFlags_SetSelected :: ImGuiTabItemFlags Source #

Trigger flag to programmatically make the tab selected when calling BeginTabItem()

pattern ImGuiTabItemFlags_UnsavedDocument :: ImGuiTabItemFlags Source #

Display a dot next to the title + tab is selected when clicking the X + closure is not assumed (will wait for user to stop submitting the tab). Otherwise closure is assumed when pressing the X, so if you keep submitting the tab may reappear at end of tab bar.

pattern ImGuiTabBarFlags_FittingPolicyScroll :: ImGuiTabBarFlags Source #

Add scroll buttons when tabs don't fit

pattern ImGuiTabBarFlags_FittingPolicyResizeDown :: ImGuiTabBarFlags Source #

Resize tabs when they don't fit

pattern ImGuiTabBarFlags_NoTooltip :: ImGuiTabBarFlags Source #

Disable tooltips when hovering a tab

pattern ImGuiTabBarFlags_NoTabListScrollingButtons :: ImGuiTabBarFlags Source #

Disable scrolling buttons (apply when fitting policy is ImGuiTabBarFlags_FittingPolicyScroll)

pattern ImGuiTabBarFlags_NoCloseWithMiddleMouseButton :: ImGuiTabBarFlags Source #

Disable behavior of closing tabs (that are submitted with p_open != NULL) with middle mouse button. You can still repro this behavior on user's side with if (IsItemHovered() && IsMouseClicked(2)) *p_open = false.

pattern ImGuiTabBarFlags_TabListPopupButton :: ImGuiTabBarFlags Source #

Disable buttons to open the tab list popup

pattern ImGuiTabBarFlags_AutoSelectNewTabs :: ImGuiTabBarFlags Source #

Automatically select new tabs when they appear

pattern ImGuiTabBarFlags_Reorderable :: ImGuiTabBarFlags Source #

Allow manually dragging tabs to re-order them + New tabs are appended at the end of list

pattern ImGuiComboFlags_NoPreview :: ImGuiComboFlags Source #

Display only a square arrow button

pattern ImGuiComboFlags_NoArrowButton :: ImGuiComboFlags Source #

Display on the preview box without the square arrow button

pattern ImGuiComboFlags_HeightLargest :: ImGuiComboFlags Source #

As many fitting items as possible

pattern ImGuiComboFlags_HeightLarge :: ImGuiComboFlags Source #

Max ~20 items visible

pattern ImGuiComboFlags_HeightRegular :: ImGuiComboFlags Source #

Max ~8 items visible (default)

pattern ImGuiComboFlags_HeightSmall :: ImGuiComboFlags Source #

Max ~4 items visible. Tip: If you want your combo popup to be a specific size you can use SetNextWindowSizeConstraints() prior to calling BeginCombo()

pattern ImGuiComboFlags_PopupAlignLeft :: ImGuiComboFlags Source #

Align the popup toward the left by default

pattern ImGuiSelectableFlags_AllowItemOverlap :: ImGuiSelectableFlags Source #

(WIP) Hit testing to allow subsequent widgets to overlap this one

pattern ImGuiSelectableFlags_Disabled :: ImGuiSelectableFlags Source #

Cannot be selected, display grayed out text

pattern ImGuiSelectableFlags_AllowDoubleClick :: ImGuiSelectableFlags Source #

Generate press events on double clicks too

pattern ImGuiSelectableFlags_SpanAllColumns :: ImGuiSelectableFlags Source #

Selectable frame can span all columns (text will still fit in current column)

pattern ImGuiSelectableFlags_DontClosePopups :: ImGuiSelectableFlags Source #

Clicking this don't close parent popup window

pattern ImGuiPopupFlags_AnyPopupLevel :: ImGuiPopupFlags Source #

For IsPopupOpen(): search/test at any level of the popup stack (default test in the current level)

pattern ImGuiPopupFlags_AnyPopupId :: ImGuiPopupFlags Source #

For IsPopupOpen(): ignore the ImGuiID parameter and test for any popup.

pattern ImGuiPopupFlags_NoOpenOverItems :: ImGuiPopupFlags Source #

For BeginPopupContextWindow(): don't return true when hovering items, only when hovering empty space

pattern ImGuiPopupFlags_NoOpenOverExistingPopup :: ImGuiPopupFlags Source #

For OpenPopup*(), BeginPopupContext*(): don't open if there's already a popup at the same level of the popup stack

pattern ImGuiPopupFlags_MouseButtonMiddle :: ImGuiPopupFlags Source #

For BeginPopupContext*(): open on Middle Mouse release. Guaranteed to always be == 2 (same as ImGuiMouseButton_Middle)

pattern ImGuiPopupFlags_MouseButtonRight :: ImGuiPopupFlags Source #

For BeginPopupContext*(): open on Right Mouse release. Guaranteed to always be == 1 (same as ImGuiMouseButton_Right)

pattern ImGuiPopupFlags_MouseButtonLeft :: ImGuiPopupFlags Source #

For BeginPopupContext*(): open on Left Mouse release. Guaranteed to always be == 0 (same as ImGuiMouseButton_Left)

pattern ImGuiTreeNodeFlags_NavLeftJumpsBackHere :: ImGuiTreeNodeFlags Source #

(WIP) Nav: left direction may move to this TreeNode() from any of its child (items submitted between TreeNode and TreePop)

pattern ImGuiTreeNodeFlags_SpanFullWidth :: ImGuiTreeNodeFlags Source #

Extend hit box to the left-most and right-most edges (bypass the indented area).

pattern ImGuiTreeNodeFlags_SpanAvailWidth :: ImGuiTreeNodeFlags Source #

Extend hit box to the right-most edge, even if not framed. This is not the default in order to allow adding other items on the same line. In the future we may refactor the hit system to be front-to-back, allowing natural overlaps and then this can become the default.

pattern ImGuiTreeNodeFlags_FramePadding :: ImGuiTreeNodeFlags Source #

Use FramePadding (even for an unframed text node) to vertically align text baseline to regular widget height. Equivalent to calling AlignTextToFramePadding().

pattern ImGuiTreeNodeFlags_Bullet :: ImGuiTreeNodeFlags Source #

Display a bullet instead of arrow

pattern ImGuiTreeNodeFlags_Leaf :: ImGuiTreeNodeFlags Source #

No collapsing, no arrow (use as a convenience for leaf nodes).

pattern ImGuiTreeNodeFlags_OpenOnArrow :: ImGuiTreeNodeFlags Source #

Only open when clicking on the arrow part. If ImGuiTreeNodeFlags_OpenOnDoubleClick is also set, single-click arrow or double-click all box to open.

pattern ImGuiTreeNodeFlags_OpenOnDoubleClick :: ImGuiTreeNodeFlags Source #

Need double-click to open node

pattern ImGuiTreeNodeFlags_DefaultOpen :: ImGuiTreeNodeFlags Source #

Default node to be open

pattern ImGuiTreeNodeFlags_NoAutoOpenOnLog :: ImGuiTreeNodeFlags Source #

Don't automatically and temporarily open node when Logging is active (by default logging will automatically open tree nodes)

pattern ImGuiTreeNodeFlags_NoTreePushOnOpen :: ImGuiTreeNodeFlags Source #

Don't do a TreePush() when open (e.g. for CollapsingHeader) = no extra indent nor pushing on ID stack

pattern ImGuiTreeNodeFlags_AllowItemOverlap :: ImGuiTreeNodeFlags Source #

Hit testing to allow subsequent widgets to overlap this one

pattern ImGuiTreeNodeFlags_Framed :: ImGuiTreeNodeFlags Source #

Draw frame with background (e.g. for CollapsingHeader)

pattern ImGuiInputTextFlags_CallbackEdit :: ImGuiInputTextFlags Source #

Callback on any edit (note that InputText() already returns true on edit, the callback is useful mainly to manipulate the underlying buffer while focus is active)

pattern ImGuiInputTextFlags_CallbackResize :: ImGuiInputTextFlags Source #

Callback on buffer capacity changes request (beyond buf_size parameter value), allowing the string to grow. Notify when the string wants to be resized (for string types which hold a cache of their Size). You will be provided a new BufSize in the callback and NEED to honor it. (see misccppimgui_stdlib.h for an example of using this)

pattern ImGuiInputTextFlags_CharsScientific :: ImGuiInputTextFlags Source #

Allow 0123456789.+-*/eE (Scientific notation input)

pattern ImGuiInputTextFlags_NoUndoRedo :: ImGuiInputTextFlags Source #

Disable undoredo. Note that input text owns the text data while active, if you want to provide your own undoredo stack you need e.g. to call ClearActiveID().

pattern ImGuiInputTextFlags_Password :: ImGuiInputTextFlags Source #

Password mode, display all characters as *

pattern ImGuiInputTextFlags_NoHorizontalScroll :: ImGuiInputTextFlags Source #

Disable following the cursor horizontally

pattern ImGuiInputTextFlags_CtrlEnterForNewLine :: ImGuiInputTextFlags Source #

In multi-line mode, unfocus with Enter, add new line with Ctrl+Enter (default is opposite: unfocus with Ctrl+Enter, add line with Enter).

pattern ImGuiInputTextFlags_AllowTabInput :: ImGuiInputTextFlags Source #

Pressing TAB input a 't' character into the text field

pattern ImGuiInputTextFlags_CallbackCharFilter :: ImGuiInputTextFlags Source #

Callback on character inputs to replace or discard them. Modify EventChar to replace or discard, or return 1 in callback to discard.

pattern ImGuiInputTextFlags_CallbackAlways :: ImGuiInputTextFlags Source #

Callback on each iteration. User code may query cursor position, modify text buffer.

pattern ImGuiInputTextFlags_CallbackHistory :: ImGuiInputTextFlags Source #

Callback on pressing Up/Down arrows (for history handling)

pattern ImGuiInputTextFlags_CallbackCompletion :: ImGuiInputTextFlags Source #

Callback on pressing TAB (for completion handling)

pattern ImGuiInputTextFlags_EnterReturnsTrue :: ImGuiInputTextFlags Source #

Return true when Enter is pressed (as opposed to every time the value was modified). Consider looking at the IsItemDeactivatedAfterEdit() function.

pattern ImGuiInputTextFlags_AutoSelectAll :: ImGuiInputTextFlags Source #

Select entire text when first taking mouse focus

pattern ImGuiInputTextFlags_CharsHexadecimal :: ImGuiInputTextFlags Source #

Allow 0123456789ABCDEFabcdef

pattern ImGuiWindowFlags_ChildMenu :: ImGuiWindowFlags Source #

Don't use! For internal use by BeginMenu()

pattern ImGuiWindowFlags_Modal :: ImGuiWindowFlags Source #

Don't use! For internal use by BeginPopupModal()

pattern ImGuiWindowFlags_Popup :: ImGuiWindowFlags Source #

Don't use! For internal use by BeginPopup()

pattern ImGuiWindowFlags_Tooltip :: ImGuiWindowFlags Source #

Don't use! For internal use by BeginTooltip()

pattern ImGuiWindowFlags_ChildWindow :: ImGuiWindowFlags Source #

Don't use! For internal use by BeginChild()

pattern ImGuiWindowFlags_NavFlattened :: ImGuiWindowFlags Source #

BETA
On child window: allow gamepad/keyboard navigation to cross over parent border to this child or between sibling child windows.

pattern ImGuiWindowFlags_UnsavedDocument :: ImGuiWindowFlags Source #

Display a dot next to the title. When used in a tab/docking context, tab is selected when clicking the X + closure is not assumed (will wait for user to stop submitting the tab). Otherwise closure is assumed when pressing the X, so if you keep submitting the tab may reappear at end of tab bar.

pattern ImGuiWindowFlags_NoNavFocus :: ImGuiWindowFlags Source #

No focusing toward this window with gamepad/keyboard navigation (e.g. skipped by CTRL+TAB)

pattern ImGuiWindowFlags_NoNavInputs :: ImGuiWindowFlags Source #

No gamepad/keyboard navigation within the window

pattern ImGuiWindowFlags_AlwaysUseWindowPadding :: ImGuiWindowFlags Source #

Ensure child windows without border uses style.WindowPadding (ignored by default for non-bordered child windows, because more convenient)

pattern ImGuiWindowFlags_AlwaysHorizontalScrollbar :: ImGuiWindowFlags Source #

Always show horizontal scrollbar (even if ContentSize.x < Size.x)

pattern ImGuiWindowFlags_AlwaysVerticalScrollbar :: ImGuiWindowFlags Source #

Always show vertical scrollbar (even if ContentSize.y < Size.y)

pattern ImGuiWindowFlags_NoBringToFrontOnFocus :: ImGuiWindowFlags Source #

Disable bringing window to front when taking focus (e.g. clicking on it or programmatically giving it focus)

pattern ImGuiWindowFlags_NoFocusOnAppearing :: ImGuiWindowFlags Source #

Disable taking focus when transitioning from hidden to visible state

pattern ImGuiWindowFlags_HorizontalScrollbar :: ImGuiWindowFlags Source #

Allow horizontal scrollbar to appear (off by default). You may use SetNextWindowContentSize(ImVec2(width,0.0f)); prior to calling Begin() to specify width. Read code in imgui_demo in the "Horizontal Scrolling" section.

pattern ImGuiWindowFlags_NoMouseInputs :: ImGuiWindowFlags Source #

Disable catching mouse, hovering test with pass through.

pattern ImGuiWindowFlags_NoSavedSettings :: ImGuiWindowFlags Source #

Never load/save settings in .ini file

pattern ImGuiWindowFlags_NoBackground :: ImGuiWindowFlags Source #

Disable drawing background color (WindowBg, etc.) and outside border. Similar as using SetNextWindowBgAlpha(0.0f).

pattern ImGuiWindowFlags_AlwaysAutoResize :: ImGuiWindowFlags Source #

Resize every window to its content every frame

pattern ImGuiWindowFlags_NoCollapse :: ImGuiWindowFlags Source #

Disable user collapsing window by double-clicking on it. Also referred to as Window Menu Button (e.g. within a docking node).

pattern ImGuiWindowFlags_NoScrollWithMouse :: ImGuiWindowFlags Source #

Disable user vertically scrolling with mouse wheel. On child window, mouse wheel will be forwarded to the parent unless NoScrollbar is also set.

pattern ImGuiWindowFlags_NoScrollbar :: ImGuiWindowFlags Source #

Disable scrollbars (window can still scroll with mouse or programmatically)

pattern ImGuiWindowFlags_NoMove :: ImGuiWindowFlags Source #

Disable user moving the window

pattern ImGuiWindowFlags_NoResize :: ImGuiWindowFlags Source #

Disable user resizing with the lower-right grip

data ImVec2 Source #

Constructors

ImVec2 

Fields

Instances

Instances details
Storable ImVec2 Source # 
Instance details

Defined in DearImGui.Structs

Show ImVec2 Source # 
Instance details

Defined in DearImGui.Structs

data ImVec3 Source #

Constructors

ImVec3 

Fields

Instances

Instances details
Storable ImVec3 Source # 
Instance details

Defined in DearImGui.Structs

Show ImVec3 Source # 
Instance details

Defined in DearImGui.Structs

data ImVec4 Source #

Constructors

ImVec4 

Fields

Instances

Instances details
Storable ImVec4 Source # 
Instance details

Defined in DearImGui.Structs

Show ImVec4 Source # 
Instance details

Defined in DearImGui.Structs

data ImGuiContext Source #

DearImGui context handle.

data ImFont Source #

Individual font handle.

data ImFontConfig Source #

Font configuration handle.

data ImFontGlyphRangesBuilder Source #

Glyph ranges builder handle.

data ImDrawList Source #

Opaque DrawList handle.

type ImGuiID = ImU32 Source #

A unique ID used by widgets (typically the result of hashing a stack of string) unsigned Integer (same as ImU32)

type ImU32 = Word32 Source #

32-bit unsigned integer (often used to store packed colors).

type ImWchar = Word32 Source #

Single wide character (used mostly in glyph management)

data ImGuiTableSortSpecs Source #

Sorting specifications for a table (often handling sort specs for a single column, occasionally more) Obtained by calling TableGetSortSpecs(). When SpecsDirty == true you can sort your data. It will be true with sorting specs have changed since last call, or the first time. Make sure to set SpecsDirty = false after sorting, else you may wastefully sort your data every frame!

data ImGuiTableColumnSortSpecs Source #

Sorting specification for one column of a table

Constructors

ImGuiTableColumnSortSpecs 

Fields