Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Main ImGui module, exporting the functions to create a GUI.
Synopsis
- newtype Context = Context (Ptr ImGuiContext)
- createContext :: MonadIO m => m Context
- destroyContext :: MonadIO m => Context -> m ()
- getCurrentContext :: MonadIO m => m Context
- setCurrentContext :: MonadIO m => Context -> m ()
- newFrame :: MonadIO m => m ()
- endFrame :: MonadIO m => m ()
- render :: MonadIO m => m ()
- newtype DrawData = DrawData (Ptr ())
- getDrawData :: MonadIO m => m DrawData
- checkVersion :: MonadIO m => m ()
- showDemoWindow :: MonadIO m => m ()
- showIDStackToolWindow :: MonadIO m => m ()
- showMetricsWindow :: MonadIO m => m ()
- showAboutWindow :: MonadIO m => m ()
- showStyleSelector :: MonadIO m => CString -> m Bool
- showFontSelector :: MonadIO m => CString -> m ()
- showUserGuide :: MonadIO m => m ()
- getVersion :: MonadIO m => m Text
- showDebugLogWindow :: MonadIO m => m ()
- logButtons :: MonadIO m => m ()
- logText :: MonadIO m => Text -> m ()
- styleColorsDark :: MonadIO m => m ()
- styleColorsLight :: MonadIO m => m ()
- styleColorsClassic :: MonadIO m => m ()
- withWindow :: MonadUnliftIO m => Text -> (Bool -> m a) -> m a
- withWindowOpen :: MonadUnliftIO m => Text -> m () -> m ()
- withCloseableWindow :: (HasSetter ref Bool, MonadUnliftIO m) => Text -> ref -> m () -> m ()
- withFullscreen :: MonadUnliftIO m => m () -> m ()
- fullscreenFlags :: ImGuiWindowFlags
- begin :: MonadIO m => Text -> m Bool
- end :: MonadIO m => m ()
- getWindowDrawList :: MonadIO m => m DrawList
- getWindowPos :: MonadIO m => m ImVec2
- getWindowSize :: MonadIO m => m ImVec2
- getWindowWidth :: MonadIO m => m CFloat
- getWindowHeight :: MonadIO m => m CFloat
- isWindowAppearing :: MonadIO m => m Bool
- isWindowCollapsed :: MonadIO m => m Bool
- isWindowFocused :: MonadIO m => ImGuiFocusedFlags -> m Bool
- setNextWindowPos :: (MonadIO m, HasGetter ref ImVec2) => ref -> ImGuiCond -> Maybe ref -> m ()
- setNextWindowSize :: (MonadIO m, HasGetter ref ImVec2) => ref -> ImGuiCond -> m ()
- setNextWindowFullscreen :: MonadIO m => m ()
- setNextWindowContentSize :: (MonadIO m, HasGetter ref ImVec2) => ref -> m ()
- setNextWindowSizeConstraints :: (MonadIO m, HasGetter ref ImVec2) => ref -> ref -> m ()
- setNextWindowCollapsed :: MonadIO m => Bool -> ImGuiCond -> m ()
- setNextWindowFocus :: MonadIO m => m ()
- setNextWindowScroll :: MonadIO m => ImVec2 -> m ()
- setNextWindowBgAlpha :: MonadIO m => Float -> m ()
- getContentRegionAvail :: MonadIO m => m ImVec2
- getContentRegionMax :: MonadIO m => m ImVec2
- getWindowContentRegionMin :: MonadIO m => m ImVec2
- getWindowContentRegionMax :: MonadIO m => m ImVec2
- withChild :: MonadUnliftIO m => Text -> ImVec2 -> Bool -> ImGuiWindowFlags -> (Bool -> m a) -> m a
- withChildOpen :: MonadUnliftIO m => Text -> ImVec2 -> Bool -> ImGuiWindowFlags -> m () -> m ()
- withChildContext :: MonadUnliftIO m => Text -> (Bool -> m a) -> m a
- beginChild :: MonadIO m => Text -> ImVec2 -> Bool -> ImGuiWindowFlags -> m Bool
- endChild :: MonadIO m => m ()
- withStyleColor :: (MonadUnliftIO m, HasGetter ref ImVec4) => ImGuiCol -> ref -> m a -> m a
- pushStyleColor :: (MonadIO m, HasGetter ref ImVec4) => ImGuiCol -> ref -> m ()
- popStyleColor :: MonadIO m => CInt -> m ()
- withStyleVar :: (MonadUnliftIO m, HasGetter ref ImVec2) => ImGuiStyleVar -> ref -> m a -> m a
- pushStyleVar :: (MonadIO m, HasGetter ref ImVec2) => ImGuiStyleVar -> ref -> m ()
- popStyleVar :: MonadIO m => Int -> m ()
- pushTabStop :: MonadIO m => CBool -> m ()
- popTabStop :: MonadIO m => m ()
- withFont :: MonadUnliftIO m => Font -> m a -> m a
- pushFont :: MonadIO m => Font -> m ()
- popFont :: MonadIO m => m ()
- data Font
- separator :: MonadIO m => m ()
- sameLine :: MonadIO m => m ()
- newLine :: MonadIO m => m ()
- spacing :: MonadIO m => m ()
- dummy :: (MonadIO m, HasGetter ref ImVec2) => ref -> m ()
- withIndent :: MonadUnliftIO m => Float -> m a -> m a
- indent :: MonadIO m => Float -> m ()
- unindent :: MonadIO m => Float -> m ()
- setNextItemWidth :: MonadIO m => Float -> m ()
- withItemWidth :: MonadUnliftIO m => Float -> m a -> m a
- pushItemWidth :: MonadIO m => Float -> m ()
- popItemWidth :: MonadIO m => m ()
- calcItemWidth :: MonadIO m => m Float
- withTextWrapPos :: MonadUnliftIO m => Float -> m a -> m a
- pushTextWrapPos :: MonadIO m => Float -> m ()
- popTextWrapPos :: MonadIO m => m ()
- withGroup :: MonadUnliftIO m => m a -> m a
- beginGroup :: MonadIO m => m ()
- endGroup :: MonadIO m => m ()
- setCursorPos :: (MonadIO m, HasGetter ref ImVec2) => ref -> m ()
- setCursorPosX :: MonadIO m => Float -> m ()
- setCursorPosY :: MonadIO m => Float -> m ()
- setCursorScreenPos :: MonadIO m => ImVec2 -> m ()
- getCursorPos :: MonadIO m => m ImVec2
- getCursorPosX :: MonadIO m => m Float
- getCursorPosY :: MonadIO m => m Float
- getCursorStartPos :: MonadIO m => m ImVec2
- alignTextToFramePadding :: MonadIO m => m ()
- getTextLineHeight :: MonadIO m => m Float
- getTextLineHeightWithSpacing :: MonadIO m => m Float
- getFrameHeight :: MonadIO m => m Float
- getFrameHeightWithSpacing :: MonadIO m => m Float
- withID :: (MonadUnliftIO m, ToID id) => id -> m a -> m a
- class ToID a where
- text :: MonadIO m => Text -> m ()
- textColored :: (HasGetter ref ImVec4, MonadIO m) => ref -> Text -> m ()
- textDisabled :: MonadIO m => Text -> m ()
- textWrapped :: MonadIO m => Text -> m ()
- labelText :: MonadIO m => Text -> Text -> m ()
- bulletText :: MonadIO m => Text -> m ()
- separatorText :: MonadIO m => Text -> m ()
- valueBool :: MonadIO m => Text -> Bool -> m ()
- valueFloat :: MonadIO m => Text -> Float -> Text -> m ()
- valueInt32 :: MonadIO m => Text -> Int32 -> m ()
- valueWord32 :: MonadIO m => Text -> Word32 -> m ()
- button :: MonadIO m => Text -> m Bool
- smallButton :: MonadIO m => Text -> m Bool
- invisibleButton :: MonadIO m => Text -> ImVec2 -> ImGuiButtonFlags -> m Bool
- arrowButton :: MonadIO m => Text -> ImGuiDir -> m Bool
- image :: MonadIO m => Ptr () -> Ptr ImVec2 -> Ptr ImVec2 -> Ptr ImVec2 -> Ptr ImVec4 -> Ptr ImVec4 -> m ()
- checkbox :: (HasSetter ref Bool, HasGetter ref Bool, MonadIO m) => Text -> ref -> m Bool
- checkboxFlags :: (HasSetter ref Int32, HasGetter ref Int32, MonadIO m) => Text -> ref -> Int32 -> m Bool
- checkboxFlagsU :: (HasSetter ref Word32, HasGetter ref Word32, MonadIO m) => Text -> ref -> Word32 -> m Bool
- radioButton :: MonadIO m => Text -> Bool -> m Bool
- radioButtonI :: (HasSetter ref Int32, HasGetter ref Int32, MonadIO m) => Text -> ref -> Int32 -> m Bool
- progressBar :: MonadIO m => Float -> Maybe Text -> m ()
- bullet :: MonadIO m => m ()
- withCombo :: MonadUnliftIO m => Text -> Text -> (Bool -> m a) -> m a
- withComboOpen :: MonadUnliftIO m => Text -> Text -> m () -> m ()
- beginCombo :: MonadIO m => Text -> Text -> m Bool
- endCombo :: MonadIO m => m ()
- combo :: (MonadIO m, HasGetter ref Int, HasSetter ref Int) => Text -> ref -> [Text] -> m Bool
- dragFloat :: (MonadIO m, HasSetter ref Float, HasGetter ref Float) => Text -> ref -> Float -> Float -> Float -> m Bool
- dragFloat2 :: (MonadIO m, HasSetter ref (Float, Float), HasGetter ref (Float, Float)) => Text -> ref -> Float -> Float -> Float -> m Bool
- dragFloat3 :: (MonadIO m, HasSetter ref (Float, Float, Float), HasGetter ref (Float, Float, Float)) => Text -> ref -> Float -> Float -> Float -> m Bool
- dragFloat4 :: (MonadIO m, HasSetter ref (Float, Float, Float, Float), HasGetter ref (Float, Float, Float, Float)) => Text -> ref -> Float -> Float -> Float -> m Bool
- dragFloatRange2 :: (MonadIO m, HasSetter ref Float, HasGetter ref Float) => Text -> ref -> ref -> Float -> Float -> Float -> Text -> Text -> m Bool
- dragInt :: (MonadIO m, HasSetter ref Int, HasGetter ref Int) => Text -> ref -> Float -> Int -> Int -> m Bool
- dragInt2 :: (MonadIO m, HasSetter ref (Int, Int), HasGetter ref (Int, Int)) => Text -> ref -> Float -> Int -> Int -> m Bool
- dragInt3 :: (MonadIO m, HasSetter ref (Int, Int, Int), HasGetter ref (Int, Int, Int)) => Text -> ref -> Float -> Int -> Int -> m Bool
- dragInt4 :: (MonadIO m, HasSetter ref (Int, Int, Int, Int), HasGetter ref (Int, Int, Int, Int)) => Text -> ref -> Float -> Int -> Int -> m Bool
- dragIntRange2 :: (MonadIO m, HasSetter ref Int, HasGetter ref Int) => Text -> ref -> ref -> Float -> Int -> Int -> Text -> Text -> m Bool
- dragScalar :: (HasSetter ref a, HasGetter ref a, HasGetter range a, Storable a, MonadIO m) => Text -> ImGuiDataType -> ref -> Float -> range -> range -> Text -> ImGuiSliderFlags -> m Bool
- dragScalarN :: (HasSetter ref [a], HasGetter ref [a], HasGetter range a, Storable a, MonadIO m) => Text -> ImGuiDataType -> ref -> Float -> range -> range -> Text -> ImGuiSliderFlags -> m Bool
- sliderFloat :: (MonadIO m, HasSetter ref Float, HasGetter ref Float) => Text -> ref -> Float -> Float -> m Bool
- sliderFloat2 :: (MonadIO m, HasSetter ref (Float, Float), HasGetter ref (Float, Float)) => Text -> ref -> Float -> Float -> m Bool
- sliderFloat3 :: (MonadIO m, HasSetter ref (Float, Float, Float), HasGetter ref (Float, Float, Float)) => Text -> ref -> Float -> Float -> m Bool
- sliderFloat4 :: (MonadIO m, HasSetter ref (Float, Float, Float, Float), HasGetter ref (Float, Float, Float, Float)) => Text -> ref -> Float -> Float -> m Bool
- sliderAngle :: (MonadIO m, HasSetter ref Float, HasGetter ref Float) => Text -> ref -> Float -> Float -> m Bool
- sliderInt :: (MonadIO m, HasSetter ref Int, HasGetter ref Int) => Text -> ref -> Int -> Int -> m Bool
- sliderInt2 :: (MonadIO m, HasSetter ref (Int, Int), HasGetter ref (Int, Int)) => Text -> ref -> Int -> Int -> m Bool
- sliderInt3 :: (MonadIO m, HasSetter ref (Int, Int, Int), HasGetter ref (Int, Int, Int)) => Text -> ref -> Int -> Int -> m Bool
- sliderInt4 :: (MonadIO m, HasSetter ref (Int, Int, Int, Int), HasGetter ref (Int, Int, Int, Int)) => Text -> ref -> Int -> Int -> m Bool
- sliderScalar :: (HasGetter ref a, HasSetter ref a, HasGetter range a, Storable a, MonadIO m) => Text -> ImGuiDataType -> ref -> range -> range -> Text -> ImGuiSliderFlags -> m Bool
- sliderScalarN :: (HasSetter value [a], HasGetter value [a], HasGetter range a, Storable a, MonadIO m) => Text -> ImGuiDataType -> value -> range -> range -> Text -> ImGuiSliderFlags -> m Bool
- vSliderFloat :: (HasSetter ref Float, HasGetter ref Float, MonadIO m) => Text -> ImVec2 -> ref -> Float -> Float -> m Bool
- vSliderInt :: (HasSetter ref Int, HasGetter ref Int, MonadIO m) => Text -> ImVec2 -> ref -> Int -> Int -> m Bool
- vSliderScalar :: (HasSetter ref a, HasGetter ref a, HasGetter range a, Storable a, MonadIO m) => Text -> ImVec2 -> ImGuiDataType -> ref -> range -> range -> Text -> ImGuiSliderFlags -> m Bool
- inputText :: (MonadIO m, HasSetter ref Text, HasGetter ref Text) => Text -> ref -> Int -> m Bool
- inputTextMultiline :: (MonadIO m, HasSetter ref Text, HasGetter ref Text) => Text -> ref -> Int -> ImVec2 -> m Bool
- inputTextWithHint :: (MonadIO m, HasSetter ref Text, HasGetter ref Text) => Text -> Text -> ref -> Int -> m Bool
- inputFloat :: (MonadIO m, HasSetter ref Float, HasGetter ref Float) => Text -> ref -> Float -> Float -> m Bool
- inputFloat2 :: (MonadIO m, HasSetter ref (Float, Float), HasGetter ref (Float, Float)) => Text -> ref -> m Bool
- inputFloat3 :: (MonadIO m, HasSetter ref (Float, Float, Float), HasGetter ref (Float, Float, Float)) => Text -> ref -> m Bool
- inputFloat4 :: (MonadIO m, HasSetter ref (Float, Float, Float, Float), HasGetter ref (Float, Float, Float, Float)) => Text -> ref -> m Bool
- inputInt :: (MonadIO m, HasSetter ref Int32, HasGetter ref Int32) => Text -> ref -> Int32 -> Int32 -> m Bool
- inputInt2 :: (MonadIO m, HasSetter ref (Int32, Int32), HasGetter ref (Int32, Int32)) => Text -> ref -> m Bool
- inputInt3 :: (MonadIO m, HasSetter ref (Int32, Int32, Int32), HasGetter ref (Int32, Int32, Int32)) => Text -> ref -> m Bool
- inputInt4 :: (MonadIO m, HasSetter ref (Int32, Int32, Int32, Int32), HasGetter ref (Int32, Int32, Int32, Int32)) => Text -> ref -> m Bool
- inputScalar :: (HasGetter ref a, HasSetter ref a, HasGetter range a, Storable a, MonadIO m) => Text -> ImGuiDataType -> ref -> range -> range -> Text -> ImGuiInputTextFlags -> m Bool
- inputScalarN :: (HasSetter value [a], HasGetter value [a], HasGetter range a, Storable a, MonadIO m) => Text -> ImGuiDataType -> value -> range -> range -> Text -> ImGuiInputTextFlags -> m Bool
- colorEdit3 :: (MonadIO m, HasSetter ref ImVec3, HasGetter ref ImVec3) => Text -> ref -> m Bool
- colorEdit4 :: (MonadIO m, HasSetter ref ImVec4, HasGetter ref ImVec4) => Text -> ref -> m Bool
- colorPicker3 :: (MonadIO m, HasSetter ref ImVec3, HasGetter ref ImVec3) => Text -> ref -> m Bool
- colorPicker4 :: (MonadIO m, HasSetter ref ImVec4, HasGetter ref ImVec4) => Text -> ref -> Maybe ImVec4 -> m Bool
- colorButton :: (MonadIO m, HasSetter ref ImVec4, HasGetter ref ImVec4) => Text -> ref -> m Bool
- setColorEditOptions :: MonadIO m => ImGuiColorEditFlags -> m ()
- withTable :: MonadUnliftIO m => TableOptions -> Text -> Int -> (Bool -> m a) -> m a
- withTableOpen :: MonadUnliftIO m => TableOptions -> Text -> Int -> m () -> m ()
- data TableOptions = TableOptions {}
- defTableOptions :: TableOptions
- beginTable :: MonadIO m => TableOptions -> Text -> Int -> m Bool
- endTable :: MonadIO m => m ()
- tableSetupColumn :: MonadIO m => Text -> m ()
- tableSetupColumnWith :: MonadIO m => TableColumnOptions -> Text -> m ()
- data TableColumnOptions = TableColumnOptions {}
- defTableColumnOptions :: TableColumnOptions
- tableHeadersRow :: MonadIO m => m ()
- tableHeader :: MonadIO m => CString -> m ()
- tableSetupScrollFreeze :: MonadIO m => Int -> Int -> m ()
- tableNextRow :: MonadIO m => m ()
- tableNextRowWith :: MonadIO m => TableRowOptions -> m ()
- data TableRowOptions = TableRowOptions {}
- defTableRowOptions :: TableRowOptions
- tableNextColumn :: MonadIO m => m () -> m ()
- tableSetColumnIndex :: MonadIO m => Int -> m Bool
- withSortableTable :: MonadIO m => (Bool -> [TableSortingSpecs] -> m ()) -> m ()
- data TableSortingSpecs = TableSortingSpecs {}
- tableGetColumnCount :: MonadIO m => m Int
- tableGetColumnIndex :: MonadIO m => m Int
- tableGetRowIndex :: MonadIO m => m Int
- tableGetColumnName :: MonadIO m => Maybe Int -> m Text
- tableGetColumnFlags :: MonadIO m => Maybe Int -> m ImGuiTableColumnFlags
- tableSetColumnEnabled :: MonadIO m => Int -> Bool -> m ()
- tableSetBgColor :: MonadIO m => ImGuiTableBgTarget -> ImU32 -> Maybe Int -> m ()
- treeNode :: MonadIO m => Text -> m Bool
- treePush :: MonadIO m => Text -> m ()
- treePop :: MonadIO m => m ()
- setNextItemOpen :: MonadIO m => Bool -> m ()
- collapsingHeader :: MonadIO m => Text -> Maybe Bool -> m Bool
- getTreeNodeToLabelSpacing :: MonadIO m => m Float
- selectable :: MonadIO m => Text -> m Bool
- selectableWith :: MonadIO m => SelectableOptions -> Text -> m Bool
- data SelectableOptions = SelectableOptions {}
- defSelectableOptions :: SelectableOptions
- listBox :: (MonadIO m, HasGetter ref Int, HasSetter ref Int) => Text -> ref -> [Text] -> m Bool
- plotLines :: MonadIO m => Text -> [CFloat] -> m ()
- plotHistogram :: MonadIO m => Text -> [CFloat] -> m ()
- withMenuBar :: MonadUnliftIO m => (Bool -> m a) -> m a
- withMenuBarOpen :: MonadUnliftIO m => m () -> m ()
- beginMenuBar :: MonadIO m => m Bool
- endMenuBar :: MonadIO m => m ()
- withMainMenuBar :: MonadUnliftIO m => (Bool -> m a) -> m a
- withMainMenuBarOpen :: MonadUnliftIO m => m () -> m ()
- beginMainMenuBar :: MonadIO m => m Bool
- endMainMenuBar :: MonadIO m => m ()
- withMenu :: MonadUnliftIO m => Text -> (Bool -> m a) -> m a
- withMenuOpen :: MonadUnliftIO m => Text -> m () -> m ()
- beginMenu :: MonadIO m => Text -> m Bool
- endMenu :: MonadIO m => m ()
- menuItem :: MonadIO m => Text -> m Bool
- withTabBar :: MonadUnliftIO m => Text -> ImGuiTabBarFlags -> (Bool -> m a) -> m a
- withTabBarOpen :: MonadUnliftIO m => Text -> ImGuiTabBarFlags -> m () -> m ()
- beginTabBar :: MonadIO m => Text -> ImGuiTabBarFlags -> m Bool
- endTabBar :: MonadIO m => m ()
- withTabItem :: (MonadUnliftIO m, HasGetter ref Bool, HasSetter ref Bool) => Text -> ref -> ImGuiTabItemFlags -> (Bool -> m a) -> m a
- withTabItemOpen :: (MonadUnliftIO m, HasGetter ref Bool, HasSetter ref Bool) => Text -> ref -> ImGuiTabItemFlags -> m () -> m ()
- beginTabItem :: (MonadIO m, HasGetter ref Bool, HasSetter ref Bool) => Text -> ref -> ImGuiTabItemFlags -> m Bool
- endTabItem :: MonadIO m => m ()
- tabItemButton :: MonadIO m => Text -> ImGuiTabItemFlags -> m Bool
- setTabItemClosed :: MonadIO m => Text -> m ()
- setItemTooltip :: MonadIO m => Text -> m ()
- withItemTooltip :: MonadUnliftIO m => m () -> m ()
- withTooltip :: MonadUnliftIO m => m () -> m ()
- beginTooltip :: MonadIO m => m Bool
- endTooltip :: MonadIO m => m ()
- withDisabled :: (MonadUnliftIO m, HasGetter ref Bool) => ref -> m a -> m a
- beginDisabled :: MonadIO m => CBool -> m ()
- endDisabled :: MonadIO m => m ()
- withPopup :: MonadUnliftIO m => Text -> (Bool -> m a) -> m a
- withPopupOpen :: MonadUnliftIO m => Text -> m () -> m ()
- beginPopup :: MonadIO m => Text -> m Bool
- endPopup :: MonadIO m => m ()
- withPopupModal :: MonadUnliftIO m => Text -> (Bool -> m a) -> m a
- withPopupModalOpen :: MonadUnliftIO m => Text -> m () -> m ()
- beginPopupModal :: MonadIO m => Text -> m Bool
- itemContextPopup :: MonadUnliftIO m => m () -> m ()
- withPopupContextItemOpen :: MonadUnliftIO m => Maybe Text -> ImGuiPopupFlags -> m () -> m ()
- withPopupContextItem :: MonadUnliftIO m => Maybe Text -> ImGuiPopupFlags -> (Bool -> m a) -> m a
- beginPopupContextItem :: MonadIO m => Maybe Text -> ImGuiPopupFlags -> m Bool
- windowContextPopup :: MonadUnliftIO m => m () -> m ()
- withPopupContextWindowOpen :: MonadUnliftIO m => Maybe Text -> ImGuiPopupFlags -> m () -> m ()
- withPopupContextWindow :: MonadUnliftIO m => Maybe Text -> ImGuiPopupFlags -> (Bool -> m a) -> m a
- beginPopupContextWindow :: MonadIO m => Maybe Text -> ImGuiPopupFlags -> m Bool
- voidContextPopup :: MonadUnliftIO m => m () -> m ()
- withPopupContextVoidOpen :: MonadUnliftIO m => Maybe Text -> ImGuiPopupFlags -> m () -> m ()
- withPopupContextVoid :: MonadUnliftIO m => Maybe Text -> ImGuiPopupFlags -> (Bool -> m a) -> m a
- beginPopupContextVoid :: MonadIO m => Maybe Text -> ImGuiPopupFlags -> m Bool
- openPopup :: MonadIO m => Text -> m ()
- openPopupOnItemClick :: MonadIO m => Text -> ImGuiPopupFlags -> m ()
- closeCurrentPopup :: MonadIO m => m ()
- isCurrentPopupOpen :: MonadIO m => Text -> m Bool
- isAnyPopupOpen :: MonadIO m => Text -> m Bool
- isAnyLevelPopupOpen :: MonadIO m => Text -> m Bool
- isItemHovered :: MonadIO m => m Bool
- isItemActive :: MonadIO m => m Bool
- isItemFocused :: MonadIO m => m Bool
- isItemClicked :: MonadIO m => ImGuiMouseButton -> m Bool
- isItemVisible :: MonadIO m => m Bool
- isItemEdited :: MonadIO m => m Bool
- isItemActivated :: MonadIO m => m Bool
- isItemDeactivated :: MonadIO m => m Bool
- isItemDeactivatedAfterEdit :: MonadIO m => m Bool
- isItemToggledOpen :: MonadIO m => m Bool
- isAnyItemHovered :: MonadIO m => m Bool
- isAnyItemActive :: MonadIO m => m Bool
- isAnyItemFocused :: MonadIO m => m Bool
- getItemID :: MonadIO m => m ImGuiID
- getItemRectMin :: MonadIO m => m ImVec2
- getItemRectMax :: MonadIO m => m ImVec2
- getItemRectSize :: MonadIO m => m ImVec2
- wantCaptureMouse :: MonadIO m => m Bool
- getMousePos :: MonadIO m => m ImVec2
- getMousePosOnOpeningCurrentPopup :: MonadIO m => m ImVec2
- isMouseDragging :: MonadIO m => ImGuiMouseButton -> CFloat -> m Bool
- getMouseDragDelta :: MonadIO m => ImGuiMouseButton -> CFloat -> m ImVec2
- resetMouseDragDelta :: MonadIO m => ImGuiMouseButton -> m ()
- wantCaptureKeyboard :: MonadIO m => m Bool
- shortcut :: MonadIO m => ImGuiKeyChord -> ImGuiInputFlags -> m Bool
- setNextItemShortcut :: MonadIO m => ImGuiKeyChord -> ImGuiInputFlags -> m ()
- setItemDefaultFocus :: MonadIO m => m ()
- setKeyboardFocusHere :: MonadIO m => CInt -> m ()
- setNextItemAllowOverlap :: MonadIO m => m ()
- withListClipper :: (ClipItems t a, MonadUnliftIO m) => Maybe Float -> t a -> (a -> m ()) -> m ()
- class ClipItems t a where
- data ClipRange a = ClipRange a a
- getBackgroundDrawList :: MonadIO m => m DrawList
- getForegroundDrawList :: MonadIO m => m DrawList
- imCol32 :: CUChar -> CUChar -> CUChar -> CUChar -> ImU32
- framerate :: MonadIO m => m Float
- getTime :: MonadIO m => m Double
- getFrameCount :: MonadIO m => m Int
- calcTextSize :: MonadIO m => Text -> Bool -> Float -> m ImVec2
- class KnownNat (Count a) => FiniteEnum a where
- newtype ImGuiWindowFlags = ImGuiWindowFlags CInt
- newtype ImGuiChildFlags = ImGuiChildFlags CInt
- newtype ImGuiInputTextFlags = ImGuiInputTextFlags CInt
- newtype ImGuiTreeNodeFlags = ImGuiTreeNodeFlags CInt
- newtype ImGuiPopupFlags = ImGuiPopupFlags CInt
- newtype ImGuiSelectableFlags = ImGuiSelectableFlags CInt
- newtype ImGuiComboFlags = ImGuiComboFlags CInt
- newtype ImGuiTabBarFlags = ImGuiTabBarFlags CInt
- newtype ImGuiTabItemFlags = ImGuiTabItemFlags CInt
- newtype ImGuiFocusedFlags = ImGuiFocusedFlags CInt
- newtype ImGuiHoveredFlags = ImGuiHoveredFlags CInt
- newtype ImGuiDragDropFlags = ImGuiDragDropFlags CInt
- newtype ImGuiDataType = ImGuiDataType CInt
- newtype ImGuiDir = ImGuiDir CInt
- newtype ImGuiSortDirection = ImGuiSortDirection CUChar
- newtype ImGuiKey = ImGuiKey CInt
- newtype ImGuiInputFlags = ImGuiInputFlags CInt
- newtype ImGuiConfigFlags = ImGuiConfigFlags CInt
- newtype ImGuiBackendFlags = ImGuiBackendFlags CInt
- newtype ImGuiCol = ImGuiCol CInt
- newtype ImGuiStyleVar = ImGuiStyleVar CInt
- newtype ImGuiButtonFlags = ImGuiButtonFlags CInt
- newtype ImGuiColorEditFlags = ImGuiColorEditFlags CInt
- newtype ImGuiSliderFlags = ImGuiSliderFlags CInt
- newtype ImGuiMouseButton = ImGuiMouseButton CInt
- newtype ImGuiMouseCursor = ImGuiMouseCursor CInt
- newtype ImGuiMouseSource = ImGuiMouseSource CInt
- newtype ImGuiCond = ImGuiCond CInt
- newtype ImGuiTableFlags = ImGuiTableFlags CInt
- newtype ImGuiTableColumnFlags = ImGuiTableColumnFlags CInt
- newtype ImGuiTableRowFlags = ImGuiTableRowFlags CInt
- newtype ImGuiTableBgTarget = ImGuiTableBgTarget CInt
- newtype ImDrawFlags = ImDrawFlags CInt
- newtype ImDrawListFlags = ImDrawListFlags CInt
- newtype ImFontAtlasFlags = ImFontAtlasFlags CInt
- pattern ImFontAtlasFlags_NoBakedLines :: ImFontAtlasFlags
- pattern ImFontAtlasFlags_NoMouseCursors :: ImFontAtlasFlags
- pattern ImFontAtlasFlags_NoPowerOfTwoHeight :: ImFontAtlasFlags
- pattern ImFontAtlasFlags_None :: ImFontAtlasFlags
- pattern ImDrawListFlags_AllowVtxOffset :: ImDrawListFlags
- pattern ImDrawListFlags_AntiAliasedFill :: ImDrawListFlags
- pattern ImDrawListFlags_AntiAliasedLinesUseTex :: ImDrawListFlags
- pattern ImDrawListFlags_AntiAliasedLines :: ImDrawListFlags
- pattern ImDrawListFlags_None :: ImDrawListFlags
- pattern ImDrawFlags_RoundCornersMask_ :: ImDrawFlags
- pattern ImDrawFlags_RoundCornersDefault_ :: ImDrawFlags
- pattern ImDrawFlags_RoundCornersAll :: ImDrawFlags
- pattern ImDrawFlags_RoundCornersRight :: ImDrawFlags
- pattern ImDrawFlags_RoundCornersLeft :: ImDrawFlags
- pattern ImDrawFlags_RoundCornersBottom :: ImDrawFlags
- pattern ImDrawFlags_RoundCornersTop :: ImDrawFlags
- pattern ImDrawFlags_RoundCornersNone :: ImDrawFlags
- pattern ImDrawFlags_RoundCornersBottomRight :: ImDrawFlags
- pattern ImDrawFlags_RoundCornersBottomLeft :: ImDrawFlags
- pattern ImDrawFlags_RoundCornersTopRight :: ImDrawFlags
- pattern ImDrawFlags_RoundCornersTopLeft :: ImDrawFlags
- pattern ImDrawFlags_Closed :: ImDrawFlags
- pattern ImDrawFlags_None :: ImDrawFlags
- pattern ImGuiTableBgTarget_CellBg :: ImGuiTableBgTarget
- pattern ImGuiTableBgTarget_RowBg1 :: ImGuiTableBgTarget
- pattern ImGuiTableBgTarget_RowBg0 :: ImGuiTableBgTarget
- pattern ImGuiTableBgTarget_None :: ImGuiTableBgTarget
- pattern ImGuiTableRowFlags_Headers :: ImGuiTableRowFlags
- pattern ImGuiTableRowFlags_None :: ImGuiTableRowFlags
- pattern ImGuiTableColumnFlags_NoDirectResize_ :: ImGuiTableColumnFlags
- pattern ImGuiTableColumnFlags_StatusMask_ :: ImGuiTableColumnFlags
- pattern ImGuiTableColumnFlags_IndentMask_ :: ImGuiTableColumnFlags
- pattern ImGuiTableColumnFlags_WidthMask_ :: ImGuiTableColumnFlags
- pattern ImGuiTableColumnFlags_IsHovered :: ImGuiTableColumnFlags
- pattern ImGuiTableColumnFlags_IsSorted :: ImGuiTableColumnFlags
- pattern ImGuiTableColumnFlags_IsVisible :: ImGuiTableColumnFlags
- pattern ImGuiTableColumnFlags_IsEnabled :: ImGuiTableColumnFlags
- pattern ImGuiTableColumnFlags_AngledHeader :: ImGuiTableColumnFlags
- pattern ImGuiTableColumnFlags_IndentDisable :: ImGuiTableColumnFlags
- pattern ImGuiTableColumnFlags_IndentEnable :: ImGuiTableColumnFlags
- pattern ImGuiTableColumnFlags_PreferSortDescending :: ImGuiTableColumnFlags
- pattern ImGuiTableColumnFlags_PreferSortAscending :: ImGuiTableColumnFlags
- pattern ImGuiTableColumnFlags_NoHeaderWidth :: ImGuiTableColumnFlags
- pattern ImGuiTableColumnFlags_NoHeaderLabel :: ImGuiTableColumnFlags
- pattern ImGuiTableColumnFlags_NoSortDescending :: ImGuiTableColumnFlags
- pattern ImGuiTableColumnFlags_NoSortAscending :: ImGuiTableColumnFlags
- pattern ImGuiTableColumnFlags_NoSort :: ImGuiTableColumnFlags
- pattern ImGuiTableColumnFlags_NoClip :: ImGuiTableColumnFlags
- pattern ImGuiTableColumnFlags_NoHide :: ImGuiTableColumnFlags
- pattern ImGuiTableColumnFlags_NoReorder :: ImGuiTableColumnFlags
- pattern ImGuiTableColumnFlags_NoResize :: ImGuiTableColumnFlags
- pattern ImGuiTableColumnFlags_WidthFixed :: ImGuiTableColumnFlags
- pattern ImGuiTableColumnFlags_WidthStretch :: ImGuiTableColumnFlags
- pattern ImGuiTableColumnFlags_DefaultSort :: ImGuiTableColumnFlags
- pattern ImGuiTableColumnFlags_DefaultHide :: ImGuiTableColumnFlags
- pattern ImGuiTableColumnFlags_Disabled :: ImGuiTableColumnFlags
- pattern ImGuiTableColumnFlags_None :: ImGuiTableColumnFlags
- pattern ImGuiTableFlags_SizingMask_ :: ImGuiTableFlags
- pattern ImGuiTableFlags_HighlightHoveredColumn :: ImGuiTableFlags
- pattern ImGuiTableFlags_SortTristate :: ImGuiTableFlags
- pattern ImGuiTableFlags_SortMulti :: ImGuiTableFlags
- pattern ImGuiTableFlags_ScrollY :: ImGuiTableFlags
- pattern ImGuiTableFlags_ScrollX :: ImGuiTableFlags
- pattern ImGuiTableFlags_NoPadInnerX :: ImGuiTableFlags
- pattern ImGuiTableFlags_NoPadOuterX :: ImGuiTableFlags
- pattern ImGuiTableFlags_PadOuterX :: ImGuiTableFlags
- pattern ImGuiTableFlags_NoClip :: ImGuiTableFlags
- pattern ImGuiTableFlags_PreciseWidths :: ImGuiTableFlags
- pattern ImGuiTableFlags_NoKeepColumnsVisible :: ImGuiTableFlags
- pattern ImGuiTableFlags_NoHostExtendY :: ImGuiTableFlags
- pattern ImGuiTableFlags_NoHostExtendX :: ImGuiTableFlags
- pattern ImGuiTableFlags_SizingStretchSame :: ImGuiTableFlags
- pattern ImGuiTableFlags_SizingStretchProp :: ImGuiTableFlags
- pattern ImGuiTableFlags_SizingFixedSame :: ImGuiTableFlags
- pattern ImGuiTableFlags_SizingFixedFit :: ImGuiTableFlags
- pattern ImGuiTableFlags_NoBordersInBodyUntilResize :: ImGuiTableFlags
- pattern ImGuiTableFlags_NoBordersInBody :: ImGuiTableFlags
- pattern ImGuiTableFlags_Borders :: ImGuiTableFlags
- pattern ImGuiTableFlags_BordersOuter :: ImGuiTableFlags
- pattern ImGuiTableFlags_BordersInner :: ImGuiTableFlags
- pattern ImGuiTableFlags_BordersV :: ImGuiTableFlags
- pattern ImGuiTableFlags_BordersH :: ImGuiTableFlags
- pattern ImGuiTableFlags_BordersOuterV :: ImGuiTableFlags
- pattern ImGuiTableFlags_BordersInnerV :: ImGuiTableFlags
- pattern ImGuiTableFlags_BordersOuterH :: ImGuiTableFlags
- pattern ImGuiTableFlags_BordersInnerH :: ImGuiTableFlags
- pattern ImGuiTableFlags_RowBg :: ImGuiTableFlags
- pattern ImGuiTableFlags_ContextMenuInBody :: ImGuiTableFlags
- pattern ImGuiTableFlags_NoSavedSettings :: ImGuiTableFlags
- pattern ImGuiTableFlags_Sortable :: ImGuiTableFlags
- pattern ImGuiTableFlags_Hideable :: ImGuiTableFlags
- pattern ImGuiTableFlags_Reorderable :: ImGuiTableFlags
- pattern ImGuiTableFlags_Resizable :: ImGuiTableFlags
- pattern ImGuiTableFlags_None :: ImGuiTableFlags
- pattern ImGuiCond_Appearing :: ImGuiCond
- pattern ImGuiCond_FirstUseEver :: ImGuiCond
- pattern ImGuiCond_Once :: ImGuiCond
- pattern ImGuiCond_Always :: ImGuiCond
- pattern ImGuiCond_None :: ImGuiCond
- pattern ImGuiMouseSource_COUNT :: ImGuiMouseSource
- pattern ImGuiMouseSource_Pen :: ImGuiMouseSource
- pattern ImGuiMouseSource_TouchScreen :: ImGuiMouseSource
- pattern ImGuiMouseSource_Mouse :: ImGuiMouseSource
- pattern ImGuiMouseCursor_NotAllowed :: ImGuiMouseCursor
- pattern ImGuiMouseCursor_Hand :: ImGuiMouseCursor
- pattern ImGuiMouseCursor_ResizeNWSE :: ImGuiMouseCursor
- pattern ImGuiMouseCursor_ResizeNESW :: ImGuiMouseCursor
- pattern ImGuiMouseCursor_ResizeEW :: ImGuiMouseCursor
- pattern ImGuiMouseCursor_ResizeNS :: ImGuiMouseCursor
- pattern ImGuiMouseCursor_ResizeAll :: ImGuiMouseCursor
- pattern ImGuiMouseCursor_TextInput :: ImGuiMouseCursor
- pattern ImGuiMouseCursor_Arrow :: ImGuiMouseCursor
- pattern ImGuiMouseCursor_None :: ImGuiMouseCursor
- pattern ImGuiMouseButton_Middle :: ImGuiMouseButton
- pattern ImGuiMouseButton_Right :: ImGuiMouseButton
- pattern ImGuiMouseButton_Left :: ImGuiMouseButton
- pattern ImGuiSliderFlags_InvalidMask_ :: ImGuiSliderFlags
- pattern ImGuiSliderFlags_WrapAround :: ImGuiSliderFlags
- pattern ImGuiSliderFlags_NoInput :: ImGuiSliderFlags
- pattern ImGuiSliderFlags_NoRoundToFormat :: ImGuiSliderFlags
- pattern ImGuiSliderFlags_Logarithmic :: ImGuiSliderFlags
- pattern ImGuiSliderFlags_AlwaysClamp :: ImGuiSliderFlags
- pattern ImGuiSliderFlags_None :: ImGuiSliderFlags
- pattern ImGuiColorEditFlags_InputMask_ :: ImGuiColorEditFlags
- pattern ImGuiColorEditFlags_PickerMask_ :: ImGuiColorEditFlags
- pattern ImGuiColorEditFlags_DataTypeMask_ :: ImGuiColorEditFlags
- pattern ImGuiColorEditFlags_DisplayMask_ :: ImGuiColorEditFlags
- pattern ImGuiColorEditFlags_DefaultOptions_ :: ImGuiColorEditFlags
- pattern ImGuiColorEditFlags_InputHSV :: ImGuiColorEditFlags
- pattern ImGuiColorEditFlags_InputRGB :: ImGuiColorEditFlags
- pattern ImGuiColorEditFlags_PickerHueWheel :: ImGuiColorEditFlags
- pattern ImGuiColorEditFlags_PickerHueBar :: ImGuiColorEditFlags
- pattern ImGuiColorEditFlags_Float :: ImGuiColorEditFlags
- pattern ImGuiColorEditFlags_Uint8 :: ImGuiColorEditFlags
- pattern ImGuiColorEditFlags_DisplayHex :: ImGuiColorEditFlags
- pattern ImGuiColorEditFlags_DisplayHSV :: ImGuiColorEditFlags
- pattern ImGuiColorEditFlags_DisplayRGB :: ImGuiColorEditFlags
- pattern ImGuiColorEditFlags_HDR :: ImGuiColorEditFlags
- pattern ImGuiColorEditFlags_AlphaPreviewHalf :: ImGuiColorEditFlags
- pattern ImGuiColorEditFlags_AlphaPreview :: ImGuiColorEditFlags
- pattern ImGuiColorEditFlags_AlphaBar :: ImGuiColorEditFlags
- pattern ImGuiColorEditFlags_NoBorder :: ImGuiColorEditFlags
- pattern ImGuiColorEditFlags_NoDragDrop :: ImGuiColorEditFlags
- pattern ImGuiColorEditFlags_NoSidePreview :: ImGuiColorEditFlags
- pattern ImGuiColorEditFlags_NoLabel :: ImGuiColorEditFlags
- pattern ImGuiColorEditFlags_NoTooltip :: ImGuiColorEditFlags
- pattern ImGuiColorEditFlags_NoInputs :: ImGuiColorEditFlags
- pattern ImGuiColorEditFlags_NoSmallPreview :: ImGuiColorEditFlags
- pattern ImGuiColorEditFlags_NoOptions :: ImGuiColorEditFlags
- pattern ImGuiColorEditFlags_NoPicker :: ImGuiColorEditFlags
- pattern ImGuiColorEditFlags_NoAlpha :: ImGuiColorEditFlags
- pattern ImGuiColorEditFlags_None :: ImGuiColorEditFlags
- pattern ImGuiButtonFlags_MouseButtonMask_ :: ImGuiButtonFlags
- pattern ImGuiButtonFlags_MouseButtonMiddle :: ImGuiButtonFlags
- pattern ImGuiButtonFlags_MouseButtonRight :: ImGuiButtonFlags
- pattern ImGuiButtonFlags_MouseButtonLeft :: ImGuiButtonFlags
- pattern ImGuiButtonFlags_None :: ImGuiButtonFlags
- pattern ImGuiStyleVar_SeparatorTextPadding :: ImGuiStyleVar
- pattern ImGuiStyleVar_SeparatorTextAlign :: ImGuiStyleVar
- pattern ImGuiStyleVar_SeparatorTextBorderSize :: ImGuiStyleVar
- pattern ImGuiStyleVar_SelectableTextAlign :: ImGuiStyleVar
- pattern ImGuiStyleVar_ButtonTextAlign :: ImGuiStyleVar
- pattern ImGuiStyleVar_TableAngledHeadersTextAlign :: ImGuiStyleVar
- pattern ImGuiStyleVar_TableAngledHeadersAngle :: ImGuiStyleVar
- pattern ImGuiStyleVar_TabBarBorderSize :: ImGuiStyleVar
- pattern ImGuiStyleVar_TabBorderSize :: ImGuiStyleVar
- pattern ImGuiStyleVar_TabRounding :: ImGuiStyleVar
- pattern ImGuiStyleVar_GrabRounding :: ImGuiStyleVar
- pattern ImGuiStyleVar_GrabMinSize :: ImGuiStyleVar
- pattern ImGuiStyleVar_ScrollbarRounding :: ImGuiStyleVar
- pattern ImGuiStyleVar_ScrollbarSize :: ImGuiStyleVar
- pattern ImGuiStyleVar_CellPadding :: ImGuiStyleVar
- pattern ImGuiStyleVar_IndentSpacing :: ImGuiStyleVar
- pattern ImGuiStyleVar_ItemInnerSpacing :: ImGuiStyleVar
- pattern ImGuiStyleVar_ItemSpacing :: ImGuiStyleVar
- pattern ImGuiStyleVar_FrameBorderSize :: ImGuiStyleVar
- pattern ImGuiStyleVar_FrameRounding :: ImGuiStyleVar
- pattern ImGuiStyleVar_FramePadding :: ImGuiStyleVar
- pattern ImGuiStyleVar_PopupBorderSize :: ImGuiStyleVar
- pattern ImGuiStyleVar_PopupRounding :: ImGuiStyleVar
- pattern ImGuiStyleVar_ChildBorderSize :: ImGuiStyleVar
- pattern ImGuiStyleVar_ChildRounding :: ImGuiStyleVar
- pattern ImGuiStyleVar_WindowTitleAlign :: ImGuiStyleVar
- pattern ImGuiStyleVar_WindowMinSize :: ImGuiStyleVar
- pattern ImGuiStyleVar_WindowBorderSize :: ImGuiStyleVar
- pattern ImGuiStyleVar_WindowRounding :: ImGuiStyleVar
- pattern ImGuiStyleVar_WindowPadding :: ImGuiStyleVar
- pattern ImGuiStyleVar_DisabledAlpha :: ImGuiStyleVar
- pattern ImGuiStyleVar_Alpha :: ImGuiStyleVar
- pattern ImGuiCol_ModalWindowDimBg :: ImGuiCol
- pattern ImGuiCol_NavWindowingDimBg :: ImGuiCol
- pattern ImGuiCol_NavWindowingHighlight :: ImGuiCol
- pattern ImGuiCol_NavHighlight :: ImGuiCol
- pattern ImGuiCol_DragDropTarget :: ImGuiCol
- pattern ImGuiCol_TextSelectedBg :: ImGuiCol
- pattern ImGuiCol_TableRowBgAlt :: ImGuiCol
- pattern ImGuiCol_TableRowBg :: ImGuiCol
- pattern ImGuiCol_TableBorderLight :: ImGuiCol
- pattern ImGuiCol_TableBorderStrong :: ImGuiCol
- pattern ImGuiCol_TableHeaderBg :: ImGuiCol
- pattern ImGuiCol_PlotHistogramHovered :: ImGuiCol
- pattern ImGuiCol_PlotHistogram :: ImGuiCol
- pattern ImGuiCol_PlotLinesHovered :: ImGuiCol
- pattern ImGuiCol_PlotLines :: ImGuiCol
- pattern ImGuiCol_TabDimmedSelectedOverline :: ImGuiCol
- pattern ImGuiCol_TabDimmedSelected :: ImGuiCol
- pattern ImGuiCol_TabDimmed :: ImGuiCol
- pattern ImGuiCol_TabSelectedOverline :: ImGuiCol
- pattern ImGuiCol_TabSelected :: ImGuiCol
- pattern ImGuiCol_Tab :: ImGuiCol
- pattern ImGuiCol_TabHovered :: ImGuiCol
- pattern ImGuiCol_ResizeGripActive :: ImGuiCol
- pattern ImGuiCol_ResizeGripHovered :: ImGuiCol
- pattern ImGuiCol_ResizeGrip :: ImGuiCol
- pattern ImGuiCol_SeparatorActive :: ImGuiCol
- pattern ImGuiCol_SeparatorHovered :: ImGuiCol
- pattern ImGuiCol_Separator :: ImGuiCol
- pattern ImGuiCol_HeaderActive :: ImGuiCol
- pattern ImGuiCol_HeaderHovered :: ImGuiCol
- pattern ImGuiCol_Header :: ImGuiCol
- pattern ImGuiCol_ButtonActive :: ImGuiCol
- pattern ImGuiCol_ButtonHovered :: ImGuiCol
- pattern ImGuiCol_Button :: ImGuiCol
- pattern ImGuiCol_SliderGrabActive :: ImGuiCol
- pattern ImGuiCol_SliderGrab :: ImGuiCol
- pattern ImGuiCol_CheckMark :: ImGuiCol
- pattern ImGuiCol_ScrollbarGrabActive :: ImGuiCol
- pattern ImGuiCol_ScrollbarGrabHovered :: ImGuiCol
- pattern ImGuiCol_ScrollbarGrab :: ImGuiCol
- pattern ImGuiCol_ScrollbarBg :: ImGuiCol
- pattern ImGuiCol_MenuBarBg :: ImGuiCol
- pattern ImGuiCol_TitleBgCollapsed :: ImGuiCol
- pattern ImGuiCol_TitleBgActive :: ImGuiCol
- pattern ImGuiCol_TitleBg :: ImGuiCol
- pattern ImGuiCol_FrameBgActive :: ImGuiCol
- pattern ImGuiCol_FrameBgHovered :: ImGuiCol
- pattern ImGuiCol_FrameBg :: ImGuiCol
- pattern ImGuiCol_BorderShadow :: ImGuiCol
- pattern ImGuiCol_Border :: ImGuiCol
- pattern ImGuiCol_PopupBg :: ImGuiCol
- pattern ImGuiCol_ChildBg :: ImGuiCol
- pattern ImGuiCol_WindowBg :: ImGuiCol
- pattern ImGuiCol_TextDisabled :: ImGuiCol
- pattern ImGuiCol_Text :: ImGuiCol
- pattern ImGuiBackendFlags_RendererHasVtxOffset :: ImGuiBackendFlags
- pattern ImGuiBackendFlags_HasSetMousePos :: ImGuiBackendFlags
- pattern ImGuiBackendFlags_HasMouseCursors :: ImGuiBackendFlags
- pattern ImGuiBackendFlags_HasGamepad :: ImGuiBackendFlags
- pattern ImGuiBackendFlags_None :: ImGuiBackendFlags
- pattern ImGuiConfigFlags_IsTouchScreen :: ImGuiConfigFlags
- pattern ImGuiConfigFlags_IsSRGB :: ImGuiConfigFlags
- pattern ImGuiConfigFlags_NoKeyboard :: ImGuiConfigFlags
- pattern ImGuiConfigFlags_NoMouseCursorChange :: ImGuiConfigFlags
- pattern ImGuiConfigFlags_NoMouse :: ImGuiConfigFlags
- pattern ImGuiConfigFlags_NavNoCaptureKeyboard :: ImGuiConfigFlags
- pattern ImGuiConfigFlags_NavEnableSetMousePos :: ImGuiConfigFlags
- pattern ImGuiConfigFlags_NavEnableGamepad :: ImGuiConfigFlags
- pattern ImGuiConfigFlags_NavEnableKeyboard :: ImGuiConfigFlags
- pattern ImGuiConfigFlags_None :: ImGuiConfigFlags
- pattern ImGuiInputFlags_Tooltip :: ImGuiInputFlags
- pattern ImGuiInputFlags_RouteFromRootWindow :: ImGuiInputFlags
- pattern ImGuiInputFlags_RouteUnlessBgFocused :: ImGuiInputFlags
- pattern ImGuiInputFlags_RouteOverActive :: ImGuiInputFlags
- pattern ImGuiInputFlags_RouteOverFocused :: ImGuiInputFlags
- pattern ImGuiInputFlags_RouteAlways :: ImGuiInputFlags
- pattern ImGuiInputFlags_RouteGlobal :: ImGuiInputFlags
- pattern ImGuiInputFlags_RouteFocused :: ImGuiInputFlags
- pattern ImGuiInputFlags_RouteActive :: ImGuiInputFlags
- pattern ImGuiInputFlags_Repeat :: ImGuiInputFlags
- pattern ImGuiInputFlags_None :: ImGuiInputFlags
- pattern ImGuiKey_NamedKey_COUNT :: ImGuiKey
- pattern ImGuiKey_NamedKey_END :: ImGuiKey
- pattern ImGuiKey_NamedKey_BEGIN :: ImGuiKey
- pattern ImGuiMod_Mask_ :: ImGuiKey
- pattern ImGuiMod_Super :: ImGuiKey
- pattern ImGuiMod_Alt :: ImGuiKey
- pattern ImGuiMod_Shift :: ImGuiKey
- pattern ImGuiMod_Ctrl :: ImGuiKey
- pattern ImGuiMod_None :: ImGuiKey
- pattern ImGuiKey_COUNT :: ImGuiKey
- pattern ImGuiKey_ReservedForModSuper :: ImGuiKey
- pattern ImGuiKey_ReservedForModAlt :: ImGuiKey
- pattern ImGuiKey_ReservedForModShift :: ImGuiKey
- pattern ImGuiKey_ReservedForModCtrl :: ImGuiKey
- pattern ImGuiKey_MouseWheelY :: ImGuiKey
- pattern ImGuiKey_MouseWheelX :: ImGuiKey
- pattern ImGuiKey_MouseX2 :: ImGuiKey
- pattern ImGuiKey_MouseX1 :: ImGuiKey
- pattern ImGuiKey_MouseMiddle :: ImGuiKey
- pattern ImGuiKey_MouseRight :: ImGuiKey
- pattern ImGuiKey_MouseLeft :: ImGuiKey
- pattern ImGuiKey_GamepadRStickDown :: ImGuiKey
- pattern ImGuiKey_GamepadRStickUp :: ImGuiKey
- pattern ImGuiKey_GamepadRStickRight :: ImGuiKey
- pattern ImGuiKey_GamepadRStickLeft :: ImGuiKey
- pattern ImGuiKey_GamepadLStickDown :: ImGuiKey
- pattern ImGuiKey_GamepadLStickUp :: ImGuiKey
- pattern ImGuiKey_GamepadLStickRight :: ImGuiKey
- pattern ImGuiKey_GamepadLStickLeft :: ImGuiKey
- pattern ImGuiKey_GamepadR3 :: ImGuiKey
- pattern ImGuiKey_GamepadL3 :: ImGuiKey
- pattern ImGuiKey_GamepadR2 :: ImGuiKey
- pattern ImGuiKey_GamepadL2 :: ImGuiKey
- pattern ImGuiKey_GamepadR1 :: ImGuiKey
- pattern ImGuiKey_GamepadL1 :: ImGuiKey
- pattern ImGuiKey_GamepadDpadDown :: ImGuiKey
- pattern ImGuiKey_GamepadDpadUp :: ImGuiKey
- pattern ImGuiKey_GamepadDpadRight :: ImGuiKey
- pattern ImGuiKey_GamepadDpadLeft :: ImGuiKey
- pattern ImGuiKey_GamepadFaceDown :: ImGuiKey
- pattern ImGuiKey_GamepadFaceUp :: ImGuiKey
- pattern ImGuiKey_GamepadFaceRight :: ImGuiKey
- pattern ImGuiKey_GamepadFaceLeft :: ImGuiKey
- pattern ImGuiKey_GamepadBack :: ImGuiKey
- pattern ImGuiKey_GamepadStart :: ImGuiKey
- pattern ImGuiKey_AppForward :: ImGuiKey
- pattern ImGuiKey_AppBack :: ImGuiKey
- pattern ImGuiKey_KeypadEqual :: ImGuiKey
- pattern ImGuiKey_KeypadEnter :: ImGuiKey
- pattern ImGuiKey_KeypadAdd :: ImGuiKey
- pattern ImGuiKey_KeypadSubtract :: ImGuiKey
- pattern ImGuiKey_KeypadMultiply :: ImGuiKey
- pattern ImGuiKey_KeypadDivide :: ImGuiKey
- pattern ImGuiKey_KeypadDecimal :: ImGuiKey
- pattern ImGuiKey_Keypad9 :: ImGuiKey
- pattern ImGuiKey_Keypad8 :: ImGuiKey
- pattern ImGuiKey_Keypad7 :: ImGuiKey
- pattern ImGuiKey_Keypad6 :: ImGuiKey
- pattern ImGuiKey_Keypad5 :: ImGuiKey
- pattern ImGuiKey_Keypad4 :: ImGuiKey
- pattern ImGuiKey_Keypad3 :: ImGuiKey
- pattern ImGuiKey_Keypad2 :: ImGuiKey
- pattern ImGuiKey_Keypad1 :: ImGuiKey
- pattern ImGuiKey_Keypad0 :: ImGuiKey
- pattern ImGuiKey_Pause :: ImGuiKey
- pattern ImGuiKey_PrintScreen :: ImGuiKey
- pattern ImGuiKey_NumLock :: ImGuiKey
- pattern ImGuiKey_ScrollLock :: ImGuiKey
- pattern ImGuiKey_CapsLock :: ImGuiKey
- pattern ImGuiKey_GraveAccent :: ImGuiKey
- pattern ImGuiKey_RightBracket :: ImGuiKey
- pattern ImGuiKey_Backslash :: ImGuiKey
- pattern ImGuiKey_LeftBracket :: ImGuiKey
- pattern ImGuiKey_Equal :: ImGuiKey
- pattern ImGuiKey_Semicolon :: ImGuiKey
- pattern ImGuiKey_Slash :: ImGuiKey
- pattern ImGuiKey_Period :: ImGuiKey
- pattern ImGuiKey_Minus :: ImGuiKey
- pattern ImGuiKey_Comma :: ImGuiKey
- pattern ImGuiKey_Apostrophe :: ImGuiKey
- pattern ImGuiKey_F24 :: ImGuiKey
- pattern ImGuiKey_F23 :: ImGuiKey
- pattern ImGuiKey_F22 :: ImGuiKey
- pattern ImGuiKey_F21 :: ImGuiKey
- pattern ImGuiKey_F20 :: ImGuiKey
- pattern ImGuiKey_F19 :: ImGuiKey
- pattern ImGuiKey_F18 :: ImGuiKey
- pattern ImGuiKey_F17 :: ImGuiKey
- pattern ImGuiKey_F16 :: ImGuiKey
- pattern ImGuiKey_F15 :: ImGuiKey
- pattern ImGuiKey_F14 :: ImGuiKey
- pattern ImGuiKey_F13 :: ImGuiKey
- pattern ImGuiKey_F12 :: ImGuiKey
- pattern ImGuiKey_F11 :: ImGuiKey
- pattern ImGuiKey_F10 :: ImGuiKey
- pattern ImGuiKey_F9 :: ImGuiKey
- pattern ImGuiKey_F8 :: ImGuiKey
- pattern ImGuiKey_F7 :: ImGuiKey
- pattern ImGuiKey_F6 :: ImGuiKey
- pattern ImGuiKey_F5 :: ImGuiKey
- pattern ImGuiKey_F4 :: ImGuiKey
- pattern ImGuiKey_F3 :: ImGuiKey
- pattern ImGuiKey_F2 :: ImGuiKey
- pattern ImGuiKey_F1 :: ImGuiKey
- pattern ImGuiKey_Z :: ImGuiKey
- pattern ImGuiKey_Y :: ImGuiKey
- pattern ImGuiKey_X :: ImGuiKey
- pattern ImGuiKey_W :: ImGuiKey
- pattern ImGuiKey_V :: ImGuiKey
- pattern ImGuiKey_U :: ImGuiKey
- pattern ImGuiKey_T :: ImGuiKey
- pattern ImGuiKey_S :: ImGuiKey
- pattern ImGuiKey_R :: ImGuiKey
- pattern ImGuiKey_Q :: ImGuiKey
- pattern ImGuiKey_P :: ImGuiKey
- pattern ImGuiKey_O :: ImGuiKey
- pattern ImGuiKey_N :: ImGuiKey
- pattern ImGuiKey_M :: ImGuiKey
- pattern ImGuiKey_L :: ImGuiKey
- pattern ImGuiKey_K :: ImGuiKey
- pattern ImGuiKey_J :: ImGuiKey
- pattern ImGuiKey_I :: ImGuiKey
- pattern ImGuiKey_H :: ImGuiKey
- pattern ImGuiKey_G :: ImGuiKey
- pattern ImGuiKey_F :: ImGuiKey
- pattern ImGuiKey_E :: ImGuiKey
- pattern ImGuiKey_D :: ImGuiKey
- pattern ImGuiKey_C :: ImGuiKey
- pattern ImGuiKey_B :: ImGuiKey
- pattern ImGuiKey_A :: ImGuiKey
- pattern ImGuiKey_9 :: ImGuiKey
- pattern ImGuiKey_8 :: ImGuiKey
- pattern ImGuiKey_7 :: ImGuiKey
- pattern ImGuiKey_6 :: ImGuiKey
- pattern ImGuiKey_5 :: ImGuiKey
- pattern ImGuiKey_4 :: ImGuiKey
- pattern ImGuiKey_3 :: ImGuiKey
- pattern ImGuiKey_2 :: ImGuiKey
- pattern ImGuiKey_1 :: ImGuiKey
- pattern ImGuiKey_0 :: ImGuiKey
- pattern ImGuiKey_Menu :: ImGuiKey
- pattern ImGuiKey_RightSuper :: ImGuiKey
- pattern ImGuiKey_RightAlt :: ImGuiKey
- pattern ImGuiKey_RightShift :: ImGuiKey
- pattern ImGuiKey_RightCtrl :: ImGuiKey
- pattern ImGuiKey_LeftSuper :: ImGuiKey
- pattern ImGuiKey_LeftAlt :: ImGuiKey
- pattern ImGuiKey_LeftShift :: ImGuiKey
- pattern ImGuiKey_LeftCtrl :: ImGuiKey
- pattern ImGuiKey_Escape :: ImGuiKey
- pattern ImGuiKey_Enter :: ImGuiKey
- pattern ImGuiKey_Space :: ImGuiKey
- pattern ImGuiKey_Backspace :: ImGuiKey
- pattern ImGuiKey_Delete :: ImGuiKey
- pattern ImGuiKey_Insert :: ImGuiKey
- pattern ImGuiKey_End :: ImGuiKey
- pattern ImGuiKey_Home :: ImGuiKey
- pattern ImGuiKey_PageDown :: ImGuiKey
- pattern ImGuiKey_PageUp :: ImGuiKey
- pattern ImGuiKey_DownArrow :: ImGuiKey
- pattern ImGuiKey_UpArrow :: ImGuiKey
- pattern ImGuiKey_RightArrow :: ImGuiKey
- pattern ImGuiKey_LeftArrow :: ImGuiKey
- pattern ImGuiKey_Tab :: ImGuiKey
- pattern ImGuiKey_None :: ImGuiKey
- pattern ImGuiSortDirection_Descending :: ImGuiSortDirection
- pattern ImGuiSortDirection_Ascending :: ImGuiSortDirection
- pattern ImGuiSortDirection_None :: ImGuiSortDirection
- pattern ImGuiDir_COUNT :: ImGuiDir
- pattern ImGuiDir_Down :: ImGuiDir
- pattern ImGuiDir_Up :: ImGuiDir
- pattern ImGuiDir_Right :: ImGuiDir
- pattern ImGuiDir_Left :: ImGuiDir
- pattern ImGuiDir_None :: ImGuiDir
- pattern ImGuiDataType_Double :: ImGuiDataType
- pattern ImGuiDataType_Float :: ImGuiDataType
- pattern ImGuiDataType_U64 :: ImGuiDataType
- pattern ImGuiDataType_S64 :: ImGuiDataType
- pattern ImGuiDataType_U32 :: ImGuiDataType
- pattern ImGuiDataType_S32 :: ImGuiDataType
- pattern ImGuiDataType_U16 :: ImGuiDataType
- pattern ImGuiDataType_S16 :: ImGuiDataType
- pattern ImGuiDataType_U8 :: ImGuiDataType
- pattern ImGuiDataType_S8 :: ImGuiDataType
- pattern ImGuiDragDropFlags_AcceptPeekOnly :: ImGuiDragDropFlags
- pattern ImGuiDragDropFlags_AcceptNoPreviewTooltip :: ImGuiDragDropFlags
- pattern ImGuiDragDropFlags_AcceptNoDrawDefaultRect :: ImGuiDragDropFlags
- pattern ImGuiDragDropFlags_AcceptBeforeDelivery :: ImGuiDragDropFlags
- pattern ImGuiDragDropFlags_PayloadNoCrossProcess :: ImGuiDragDropFlags
- pattern ImGuiDragDropFlags_PayloadNoCrossContext :: ImGuiDragDropFlags
- pattern ImGuiDragDropFlags_PayloadAutoExpire :: ImGuiDragDropFlags
- pattern ImGuiDragDropFlags_SourceExtern :: ImGuiDragDropFlags
- pattern ImGuiDragDropFlags_SourceAllowNullID :: ImGuiDragDropFlags
- pattern ImGuiDragDropFlags_SourceNoHoldToOpenOthers :: ImGuiDragDropFlags
- pattern ImGuiDragDropFlags_SourceNoDisableHover :: ImGuiDragDropFlags
- pattern ImGuiDragDropFlags_SourceNoPreviewTooltip :: ImGuiDragDropFlags
- pattern ImGuiDragDropFlags_None :: ImGuiDragDropFlags
- pattern ImGuiHoveredFlags_NoSharedDelay :: ImGuiHoveredFlags
- pattern ImGuiHoveredFlags_DelayNormal :: ImGuiHoveredFlags
- pattern ImGuiHoveredFlags_DelayShort :: ImGuiHoveredFlags
- pattern ImGuiHoveredFlags_DelayNone :: ImGuiHoveredFlags
- pattern ImGuiHoveredFlags_Stationary :: ImGuiHoveredFlags
- pattern ImGuiHoveredFlags_ForTooltip :: ImGuiHoveredFlags
- pattern ImGuiHoveredFlags_RootAndChildWindows :: ImGuiHoveredFlags
- pattern ImGuiHoveredFlags_RectOnly :: ImGuiHoveredFlags
- pattern ImGuiHoveredFlags_AllowWhenOverlapped :: ImGuiHoveredFlags
- pattern ImGuiHoveredFlags_NoNavOverride :: ImGuiHoveredFlags
- pattern ImGuiHoveredFlags_AllowWhenDisabled :: ImGuiHoveredFlags
- pattern ImGuiHoveredFlags_AllowWhenOverlappedByWindow :: ImGuiHoveredFlags
- pattern ImGuiHoveredFlags_AllowWhenOverlappedByItem :: ImGuiHoveredFlags
- pattern ImGuiHoveredFlags_AllowWhenBlockedByActiveItem :: ImGuiHoveredFlags
- pattern ImGuiHoveredFlags_AllowWhenBlockedByPopup :: ImGuiHoveredFlags
- pattern ImGuiHoveredFlags_NoPopupHierarchy :: ImGuiHoveredFlags
- pattern ImGuiHoveredFlags_AnyWindow :: ImGuiHoveredFlags
- pattern ImGuiHoveredFlags_RootWindow :: ImGuiHoveredFlags
- pattern ImGuiHoveredFlags_ChildWindows :: ImGuiHoveredFlags
- pattern ImGuiHoveredFlags_None :: ImGuiHoveredFlags
- pattern ImGuiFocusedFlags_RootAndChildWindows :: ImGuiFocusedFlags
- pattern ImGuiFocusedFlags_NoPopupHierarchy :: ImGuiFocusedFlags
- pattern ImGuiFocusedFlags_AnyWindow :: ImGuiFocusedFlags
- pattern ImGuiFocusedFlags_RootWindow :: ImGuiFocusedFlags
- pattern ImGuiFocusedFlags_ChildWindows :: ImGuiFocusedFlags
- pattern ImGuiFocusedFlags_None :: ImGuiFocusedFlags
- pattern ImGuiTabItemFlags_NoAssumedClosure :: ImGuiTabItemFlags
- pattern ImGuiTabItemFlags_Trailing :: ImGuiTabItemFlags
- pattern ImGuiTabItemFlags_Leading :: ImGuiTabItemFlags
- pattern ImGuiTabItemFlags_NoReorder :: ImGuiTabItemFlags
- pattern ImGuiTabItemFlags_NoTooltip :: ImGuiTabItemFlags
- pattern ImGuiTabItemFlags_NoPushId :: ImGuiTabItemFlags
- pattern ImGuiTabItemFlags_NoCloseWithMiddleMouseButton :: ImGuiTabItemFlags
- pattern ImGuiTabItemFlags_SetSelected :: ImGuiTabItemFlags
- pattern ImGuiTabItemFlags_UnsavedDocument :: ImGuiTabItemFlags
- pattern ImGuiTabItemFlags_None :: ImGuiTabItemFlags
- pattern ImGuiTabBarFlags_FittingPolicyDefault_ :: ImGuiTabBarFlags
- pattern ImGuiTabBarFlags_FittingPolicyMask_ :: ImGuiTabBarFlags
- pattern ImGuiTabBarFlags_FittingPolicyScroll :: ImGuiTabBarFlags
- pattern ImGuiTabBarFlags_FittingPolicyResizeDown :: ImGuiTabBarFlags
- pattern ImGuiTabBarFlags_DrawSelectedOverline :: ImGuiTabBarFlags
- pattern ImGuiTabBarFlags_NoTooltip :: ImGuiTabBarFlags
- pattern ImGuiTabBarFlags_NoTabListScrollingButtons :: ImGuiTabBarFlags
- pattern ImGuiTabBarFlags_NoCloseWithMiddleMouseButton :: ImGuiTabBarFlags
- pattern ImGuiTabBarFlags_TabListPopupButton :: ImGuiTabBarFlags
- pattern ImGuiTabBarFlags_AutoSelectNewTabs :: ImGuiTabBarFlags
- pattern ImGuiTabBarFlags_Reorderable :: ImGuiTabBarFlags
- pattern ImGuiTabBarFlags_None :: ImGuiTabBarFlags
- pattern ImGuiComboFlags_HeightMask_ :: ImGuiComboFlags
- pattern ImGuiComboFlags_WidthFitPreview :: ImGuiComboFlags
- pattern ImGuiComboFlags_NoPreview :: ImGuiComboFlags
- pattern ImGuiComboFlags_NoArrowButton :: ImGuiComboFlags
- pattern ImGuiComboFlags_HeightLargest :: ImGuiComboFlags
- pattern ImGuiComboFlags_HeightLarge :: ImGuiComboFlags
- pattern ImGuiComboFlags_HeightRegular :: ImGuiComboFlags
- pattern ImGuiComboFlags_HeightSmall :: ImGuiComboFlags
- pattern ImGuiComboFlags_PopupAlignLeft :: ImGuiComboFlags
- pattern ImGuiComboFlags_None :: ImGuiComboFlags
- pattern ImGuiSelectableFlags_AllowOverlap :: ImGuiSelectableFlags
- pattern ImGuiSelectableFlags_Disabled :: ImGuiSelectableFlags
- pattern ImGuiSelectableFlags_AllowDoubleClick :: ImGuiSelectableFlags
- pattern ImGuiSelectableFlags_SpanAllColumns :: ImGuiSelectableFlags
- pattern ImGuiSelectableFlags_DontClosePopups :: ImGuiSelectableFlags
- pattern ImGuiSelectableFlags_None :: ImGuiSelectableFlags
- pattern ImGuiPopupFlags_AnyPopup :: ImGuiPopupFlags
- pattern ImGuiPopupFlags_AnyPopupLevel :: ImGuiPopupFlags
- pattern ImGuiPopupFlags_AnyPopupId :: ImGuiPopupFlags
- pattern ImGuiPopupFlags_NoOpenOverItems :: ImGuiPopupFlags
- pattern ImGuiPopupFlags_NoOpenOverExistingPopup :: ImGuiPopupFlags
- pattern ImGuiPopupFlags_NoReopen :: ImGuiPopupFlags
- pattern ImGuiPopupFlags_MouseButtonDefault_ :: ImGuiPopupFlags
- pattern ImGuiPopupFlags_MouseButtonMask_ :: ImGuiPopupFlags
- pattern ImGuiPopupFlags_MouseButtonMiddle :: ImGuiPopupFlags
- pattern ImGuiPopupFlags_MouseButtonRight :: ImGuiPopupFlags
- pattern ImGuiPopupFlags_MouseButtonLeft :: ImGuiPopupFlags
- pattern ImGuiPopupFlags_None :: ImGuiPopupFlags
- pattern ImGuiTreeNodeFlags_CollapsingHeader :: ImGuiTreeNodeFlags
- pattern ImGuiTreeNodeFlags_NavLeftJumpsBackHere :: ImGuiTreeNodeFlags
- pattern ImGuiTreeNodeFlags_SpanAllColumns :: ImGuiTreeNodeFlags
- pattern ImGuiTreeNodeFlags_SpanTextWidth :: ImGuiTreeNodeFlags
- pattern ImGuiTreeNodeFlags_SpanFullWidth :: ImGuiTreeNodeFlags
- pattern ImGuiTreeNodeFlags_SpanAvailWidth :: ImGuiTreeNodeFlags
- pattern ImGuiTreeNodeFlags_FramePadding :: ImGuiTreeNodeFlags
- pattern ImGuiTreeNodeFlags_Bullet :: ImGuiTreeNodeFlags
- pattern ImGuiTreeNodeFlags_Leaf :: ImGuiTreeNodeFlags
- pattern ImGuiTreeNodeFlags_OpenOnArrow :: ImGuiTreeNodeFlags
- pattern ImGuiTreeNodeFlags_OpenOnDoubleClick :: ImGuiTreeNodeFlags
- pattern ImGuiTreeNodeFlags_DefaultOpen :: ImGuiTreeNodeFlags
- pattern ImGuiTreeNodeFlags_NoAutoOpenOnLog :: ImGuiTreeNodeFlags
- pattern ImGuiTreeNodeFlags_NoTreePushOnOpen :: ImGuiTreeNodeFlags
- pattern ImGuiTreeNodeFlags_AllowOverlap :: ImGuiTreeNodeFlags
- pattern ImGuiTreeNodeFlags_Framed :: ImGuiTreeNodeFlags
- pattern ImGuiTreeNodeFlags_Selected :: ImGuiTreeNodeFlags
- pattern ImGuiTreeNodeFlags_None :: ImGuiTreeNodeFlags
- pattern ImGuiInputTextFlags_CallbackEdit :: ImGuiInputTextFlags
- pattern ImGuiInputTextFlags_CallbackResize :: ImGuiInputTextFlags
- pattern ImGuiInputTextFlags_CallbackCharFilter :: ImGuiInputTextFlags
- pattern ImGuiInputTextFlags_CallbackAlways :: ImGuiInputTextFlags
- pattern ImGuiInputTextFlags_CallbackHistory :: ImGuiInputTextFlags
- pattern ImGuiInputTextFlags_CallbackCompletion :: ImGuiInputTextFlags
- pattern ImGuiInputTextFlags_NoUndoRedo :: ImGuiInputTextFlags
- pattern ImGuiInputTextFlags_NoHorizontalScroll :: ImGuiInputTextFlags
- pattern ImGuiInputTextFlags_DisplayEmptyRefVal :: ImGuiInputTextFlags
- pattern ImGuiInputTextFlags_ParseEmptyRefVal :: ImGuiInputTextFlags
- pattern ImGuiInputTextFlags_AutoSelectAll :: ImGuiInputTextFlags
- pattern ImGuiInputTextFlags_AlwaysOverwrite :: ImGuiInputTextFlags
- pattern ImGuiInputTextFlags_Password :: ImGuiInputTextFlags
- pattern ImGuiInputTextFlags_ReadOnly :: ImGuiInputTextFlags
- pattern ImGuiInputTextFlags_CtrlEnterForNewLine :: ImGuiInputTextFlags
- pattern ImGuiInputTextFlags_EscapeClearsAll :: ImGuiInputTextFlags
- pattern ImGuiInputTextFlags_EnterReturnsTrue :: ImGuiInputTextFlags
- pattern ImGuiInputTextFlags_AllowTabInput :: ImGuiInputTextFlags
- pattern ImGuiInputTextFlags_CharsNoBlank :: ImGuiInputTextFlags
- pattern ImGuiInputTextFlags_CharsUppercase :: ImGuiInputTextFlags
- pattern ImGuiInputTextFlags_CharsScientific :: ImGuiInputTextFlags
- pattern ImGuiInputTextFlags_CharsHexadecimal :: ImGuiInputTextFlags
- pattern ImGuiInputTextFlags_CharsDecimal :: ImGuiInputTextFlags
- pattern ImGuiInputTextFlags_None :: ImGuiInputTextFlags
- pattern ImGuiChildFlags_NavFlattened :: ImGuiChildFlags
- pattern ImGuiChildFlags_FrameStyle :: ImGuiChildFlags
- pattern ImGuiChildFlags_AlwaysAutoResize :: ImGuiChildFlags
- pattern ImGuiChildFlags_AutoResizeY :: ImGuiChildFlags
- pattern ImGuiChildFlags_AutoResizeX :: ImGuiChildFlags
- pattern ImGuiChildFlags_ResizeY :: ImGuiChildFlags
- pattern ImGuiChildFlags_ResizeX :: ImGuiChildFlags
- pattern ImGuiChildFlags_AlwaysUseWindowPadding :: ImGuiChildFlags
- pattern ImGuiChildFlags_Border :: ImGuiChildFlags
- pattern ImGuiChildFlags_None :: ImGuiChildFlags
- pattern ImGuiWindowFlags_ChildMenu :: ImGuiWindowFlags
- pattern ImGuiWindowFlags_Modal :: ImGuiWindowFlags
- pattern ImGuiWindowFlags_Popup :: ImGuiWindowFlags
- pattern ImGuiWindowFlags_Tooltip :: ImGuiWindowFlags
- pattern ImGuiWindowFlags_ChildWindow :: ImGuiWindowFlags
- pattern ImGuiWindowFlags_NoInputs :: ImGuiWindowFlags
- pattern ImGuiWindowFlags_NoDecoration :: ImGuiWindowFlags
- pattern ImGuiWindowFlags_NoNav :: ImGuiWindowFlags
- pattern ImGuiWindowFlags_UnsavedDocument :: ImGuiWindowFlags
- pattern ImGuiWindowFlags_NoNavFocus :: ImGuiWindowFlags
- pattern ImGuiWindowFlags_NoNavInputs :: ImGuiWindowFlags
- pattern ImGuiWindowFlags_AlwaysHorizontalScrollbar :: ImGuiWindowFlags
- pattern ImGuiWindowFlags_AlwaysVerticalScrollbar :: ImGuiWindowFlags
- pattern ImGuiWindowFlags_NoBringToFrontOnFocus :: ImGuiWindowFlags
- pattern ImGuiWindowFlags_NoFocusOnAppearing :: ImGuiWindowFlags
- pattern ImGuiWindowFlags_HorizontalScrollbar :: ImGuiWindowFlags
- pattern ImGuiWindowFlags_MenuBar :: ImGuiWindowFlags
- pattern ImGuiWindowFlags_NoMouseInputs :: ImGuiWindowFlags
- pattern ImGuiWindowFlags_NoSavedSettings :: ImGuiWindowFlags
- pattern ImGuiWindowFlags_NoBackground :: ImGuiWindowFlags
- pattern ImGuiWindowFlags_AlwaysAutoResize :: ImGuiWindowFlags
- pattern ImGuiWindowFlags_NoCollapse :: ImGuiWindowFlags
- pattern ImGuiWindowFlags_NoScrollWithMouse :: ImGuiWindowFlags
- pattern ImGuiWindowFlags_NoScrollbar :: ImGuiWindowFlags
- pattern ImGuiWindowFlags_NoMove :: ImGuiWindowFlags
- pattern ImGuiWindowFlags_NoResize :: ImGuiWindowFlags
- pattern ImGuiWindowFlags_NoTitleBar :: ImGuiWindowFlags
- pattern ImGuiWindowFlags_None :: ImGuiWindowFlags
- data ImVec2 = ImVec2 {}
- data ImVec3 = ImVec3 {}
- data ImVec4 = ImVec4 {}
- data ImGuiContext
- data ImFont
- data ImFontConfig
- data ImFontGlyphRangesBuilder
- data ImDrawList
- data ImGuiListClipper
- data ImGuiPayload
- type ImGuiID = ImU32
- type ImU32 = Word32
- type ImS16 = Int16
- type ImWchar = Word32
- data ImGuiTableSortSpecs = ImGuiTableSortSpecs {}
- data ImGuiTableColumnSortSpecs = ImGuiTableColumnSortSpecs {}
Context Creation and Access
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
render :: MonadIO m => m () Source #
Ends the Dear ImGui frame, finalize the draw data. You can then get call
getDrawData
.
getDrawData :: MonadIO m => m DrawData Source #
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!
showIDStackToolWindow :: MonadIO m => m () Source #
Create Stack Tool window. hover items with mouse to query information about the source of their unique ID.
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.
showStyleSelector :: MonadIO m => CString -> m Bool Source #
Add style selector block (not a window), essentially a combo listing the default styles.
showFontSelector :: MonadIO m => CString -> m () Source #
Add font selector block (not a window), essentially a combo listing the loaded fonts.
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
).
Logging
showDebugLogWindow :: MonadIO m => m () Source #
Create Debug Log window. display a simplified log of important dear imgui events.
logButtons :: MonadIO m => m () Source #
Helper to display buttons for logging to ttyfileclipboard.
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.
withCloseableWindow :: (HasSetter ref Bool, MonadUnliftIO m) => Text -> ref -> m () -> m () Source #
Append items to a closeable 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.
The Bool
state variable will be set to False
when the window's close
button is pressed.
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.
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.
getWindowSize :: MonadIO m => m ImVec2 Source #
getWindowWidth :: MonadIO m => m CFloat Source #
getWindowHeight :: MonadIO m => m CFloat Source #
isWindowAppearing :: MonadIO m => m Bool Source #
isWindowCollapsed :: MonadIO m => m Bool Source #
isWindowFocused :: MonadIO m => ImGuiFocusedFlags -> m Bool Source #
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()
setNextWindowFocus :: MonadIO m => m () Source #
Set next window to be focused / top-most. call before begin
setNextWindowScroll :: MonadIO m => ImVec2 -> m () Source #
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()
getContentRegionAvail :: MonadIO m => m ImVec2 Source #
Retrieve available space from a given point.
== GetContentRegionMax() - GetCursorPos()
getContentRegionMax :: MonadIO m => m ImVec2 Source #
Current content boundaries (typically window boundaries including scrolling, or current column boundaries), in window coordinates.
getWindowContentRegionMin :: MonadIO m => m ImVec2 Source #
Content boundaries min for the full window (roughly (0,0) - Scroll
), in window coordinates.
getWindowContentRegionMax :: MonadIO m => m ImVec2 Source #
Content boundaries max for the full window (roughly (0,0) + Size - Scroll
) where Size can be overridden with SetNextWindowContentSize(), in window coordinates.
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()
.
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()
pushTabStop :: MonadIO m => CBool -> m () Source #
Allow focusing using TAB/Shift-TAB, enabled by default but you can disable it for certain widgets.
popTabStop :: MonadIO m => m () Source #
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.
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()
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 #
pushItemWidth :: MonadIO m => Float -> m () Source #
popItemWidth :: MonadIO m => m () Source #
calcItemWidth :: MonadIO m => m Float Source #
Width of item given pushed settings and current cursor position. NOT necessarily the width of last item unlike most Item functions.
withTextWrapPos :: MonadUnliftIO m => Float -> m a -> m a Source #
pushTextWrapPos :: MonadIO m => Float -> m () Source #
Push word-wrapping position for Text commands.
Negative: no wrapping.
Zero: wrap to end of window (or column).
Positive: wrap at wrap_pos_x
position in window local space.
popTextWrapPos :: MonadIO m => m () 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()
setCursorPosX :: MonadIO m => Float -> m () Source #
setCursorPosY :: MonadIO m => Float -> m () Source #
setCursorScreenPos :: MonadIO m => ImVec2 -> m () Source #
getCursorPos :: MonadIO m => m ImVec2 Source #
Get cursor position in window-local coordinates.
Useful to overlap draw using setCursorPos
.
Wraps ImGui::SetCursorPos()
getCursorPosX :: MonadIO m => m Float Source #
getCursorPosY :: MonadIO m => m Float Source #
getCursorStartPos :: MonadIO m => m ImVec2 Source #
Initial cursor position, in window coordinates.
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()
getTextLineHeight :: MonadIO m => m Float Source #
getTextLineHeightWithSpacing :: MonadIO m => m Float Source #
getFrameHeight :: MonadIO m => m Float Source #
getFrameHeightWithSpacing :: MonadIO m => m Float Source #
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
A supplementary class to match overloaded functions in C++ the library.
Widgets
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.
separatorText :: MonadIO m => Text -> m () Source #
Text with an horizontal line.
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()
.
checkboxFlags :: (HasSetter ref Int32, HasGetter ref Int32, MonadIO m) => Text -> ref -> Int32 -> m Bool Source #
Checkbox for a bit mask inside a signed value.
checkboxFlagsU :: (HasSetter ref Word32, HasGetter ref Word32, MonadIO m) => Text -> ref -> Word32 -> m Bool Source #
Checkbox for a bit mask inside an unsigned value.
radioButtonI :: (HasSetter ref Int32, HasGetter ref Int32, MonadIO m) => Text -> ref -> Int32 -> m Bool Source #
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()
.
inputFloat :: (MonadIO m, HasSetter ref Float, HasGetter ref Float) => Text -> ref -> Float -> Float -> m Bool Source #
inputFloat2 :: (MonadIO m, HasSetter ref (Float, Float), HasGetter ref (Float, Float)) => Text -> ref -> m Bool Source #
inputFloat3 :: (MonadIO m, HasSetter ref (Float, Float, Float), HasGetter ref (Float, Float, Float)) => Text -> ref -> m Bool Source #
inputFloat4 :: (MonadIO m, HasSetter ref (Float, Float, Float, Float), HasGetter ref (Float, Float, Float, Float)) => Text -> ref -> m Bool Source #
inputInt :: (MonadIO m, HasSetter ref Int32, HasGetter ref Int32) => Text -> ref -> Int32 -> Int32 -> m Bool Source #
inputInt2 :: (MonadIO m, HasSetter ref (Int32, Int32), HasGetter ref (Int32, Int32)) => Text -> ref -> m Bool Source #
inputInt3 :: (MonadIO m, HasSetter ref (Int32, Int32, Int32), HasGetter ref (Int32, Int32, Int32)) => Text -> ref -> m Bool Source #
inputInt4 :: (MonadIO m, HasSetter ref (Int32, Int32, Int32, Int32), HasGetter ref (Int32, Int32, Int32, Int32)) => Text -> ref -> m Bool Source #
inputScalar :: (HasGetter ref a, HasSetter ref a, HasGetter range a, Storable a, MonadIO m) => Text -> ImGuiDataType -> ref -> range -> range -> Text -> ImGuiInputTextFlags -> m Bool Source #
inputScalarN :: (HasSetter value [a], HasGetter value [a], HasGetter range a, Storable a, MonadIO m) => Text -> ImGuiDataType -> value -> range -> range -> Text -> ImGuiInputTextFlags -> m Bool Source #
Color Editor/Picker
colorEdit3 :: (MonadIO m, HasSetter ref ImVec3, HasGetter ref ImVec3) => Text -> ref -> m Bool Source #
Wraps ImGui::ColorPicker3()
.
colorEdit4 :: (MonadIO m, HasSetter ref ImVec4, HasGetter ref ImVec4) => Text -> ref -> m Bool Source #
Wraps ImGui::ColorEdit3()
.
colorPicker3 :: (MonadIO m, HasSetter ref ImVec3, HasGetter ref ImVec3) => Text -> ref -> m Bool Source #
Wraps ImGui::ColorPicker3()
.
colorPicker4 :: (MonadIO m, HasSetter ref ImVec4, HasGetter ref ImVec4) => Text -> ref -> Maybe ImVec4 -> 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()
.
setColorEditOptions :: MonadIO m => ImGuiColorEditFlags -> m () Source #
Initialize current options (generally on application startup) if you want to select a default format, picker type, etc.
User will be able to change many settings, unless you pass the ImGuiColorEditFlags_NoOptions
flag to your calls.
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:
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
Show TableOptions Source # | |
Defined in DearImGui showsPrec :: Int -> TableOptions -> ShowS # show :: TableOptions -> String # showList :: [TableOptions] -> ShowS # |
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
.
data TableColumnOptions Source #
Instances
Show TableColumnOptions Source # | |
Defined in DearImGui showsPrec :: Int -> TableColumnOptions -> ShowS # show :: TableColumnOptions -> String # showList :: [TableColumnOptions] -> ShowS # |
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.
data TableRowOptions Source #
Instances
Show TableRowOptions Source # | |
Defined in DearImGui showsPrec :: Int -> TableRowOptions -> ShowS # show :: TableRowOptions -> String # showList :: [TableRowOptions] -> ShowS # |
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:
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
data TableSortingSpecs Source #
TableSortingSpecs | |
|
Instances
Show TableSortingSpecs Source # | |
Defined in DearImGui showsPrec :: Int -> TableSortingSpecs -> ShowS # show :: TableSortingSpecs -> String # showList :: [TableSortingSpecs] -> ShowS # | |
Eq TableSortingSpecs Source # | |
Defined in DearImGui (==) :: TableSortingSpecs -> TableSortingSpecs -> Bool # (/=) :: TableSortingSpecs -> TableSortingSpecs -> Bool # | |
Ord TableSortingSpecs Source # | |
Defined in DearImGui compare :: TableSortingSpecs -> TableSortingSpecs -> Ordering # (<) :: TableSortingSpecs -> TableSortingSpecs -> Bool # (<=) :: TableSortingSpecs -> TableSortingSpecs -> Bool # (>) :: TableSortingSpecs -> TableSortingSpecs -> Bool # (>=) :: TableSortingSpecs -> TableSortingSpecs -> Bool # max :: TableSortingSpecs -> TableSortingSpecs -> TableSortingSpecs # min :: TableSortingSpecs -> TableSortingSpecs -> TableSortingSpecs # |
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
setNextItemOpen :: MonadIO m => Bool -> m () Source #
Wraps ImGui::SetNextItemOpen()
.
getTreeNodeToLabelSpacing :: MonadIO m => m Float Source #
Selectables
selectableWith :: MonadIO m => SelectableOptions -> Text -> m Bool Source #
Wraps ImGui::Selectable()
with explicit options.
data SelectableOptions Source #
Instances
Show SelectableOptions Source # | |
Defined in DearImGui showsPrec :: Int -> SelectableOptions -> ShowS # show :: SelectableOptions -> String # showList :: [SelectableOptions] -> ShowS # |
List Boxes
listBox :: (MonadIO m, HasGetter ref Int, HasSetter ref Int) => Text -> ref -> [Text] -> m Bool Source #
Data Plotting
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.
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 -> ImGuiTabItemFlags -> (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 -> ImGuiTabItemFlags -> 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 -> ImGuiTabItemFlags -> 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
setItemTooltip :: MonadIO m => Text -> m () Source #
Set a text-only tooltip if preceding item was hovered.
withItemTooltip :: MonadUnliftIO m => m () -> m () Source #
Create a tooltip if a previous item is hovered.
Those are windows that follow a mouse and don't take focus away. Can contain any kind of items.
withTooltip :: MonadUnliftIO m => m () -> m () 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 Bool Source #
Begin/append a tooltip window to create full-featured tooltip (with any kind of items).
endTooltip :: MonadIO m => m () Source #
Only call if beginTooltip
/beginItemTooltip
returns True!
Disabled blocks
withDisabled :: (MonadUnliftIO m, HasGetter ref Bool) => ref -> m a -> m a Source #
Action wrapper for disabled blocks.
See beginDisabled
and endDisabled
for more info.
beginDisabled :: MonadIO m => CBool -> m () Source #
Begin a block that may be disabled. This disables all user interactions and dims item visuals.
Always call a matching endDisabled
for each beginDisabled
call.
The boolean argument is only intended to facilitate use of boolean
expressions. If you can avoid calling beginDisabled 0
altogether,
that should be preferred.
Wraps ImGui::BeginDisabled()
endDisabled :: MonadIO m => m () Source #
Ends a block that may be disabled.
Wraps ImGui::EndDisabled()
Popups/Modals
Generic
withPopup :: MonadUnliftIO m => Text -> (Bool -> m a) -> m a Source #
Append items 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 items 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 items 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 #
beginPopupContextItem :: MonadIO m => Maybe Text -> ImGuiPopupFlags -> m Bool 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 #
beginPopupContextWindow :: MonadIO m => Maybe Text -> ImGuiPopupFlags -> m Bool 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 #
beginPopupContextVoid :: MonadIO m => Maybe Text -> ImGuiPopupFlags -> m Bool 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()
isItemActive :: MonadIO m => m Bool Source #
Is the last item hovered? (and usable, aka not blocked by a popup, etc.).
isItemFocused :: MonadIO m => m Bool Source #
isItemClicked :: MonadIO m => ImGuiMouseButton -> m Bool Source #
isItemVisible :: MonadIO m => m Bool Source #
isItemEdited :: MonadIO m => m Bool Source #
isItemActivated :: MonadIO m => m Bool Source #
isItemDeactivated :: MonadIO m => m Bool Source #
isItemDeactivatedAfterEdit :: MonadIO m => m Bool Source #
isItemToggledOpen :: MonadIO m => m Bool Source #
isAnyItemHovered :: MonadIO m => m Bool Source #
isAnyItemActive :: MonadIO m => m Bool Source #
Is the last item hovered? (and usable, aka not blocked by a popup, etc.).
isAnyItemFocused :: MonadIO m => m Bool Source #
getItemRectMin :: MonadIO m => m ImVec2 Source #
getItemRectMax :: MonadIO m => m ImVec2 Source #
getItemRectSize :: MonadIO m => m ImVec2 Source #
Utilities
wantCaptureMouse :: MonadIO m => m Bool Source #
getMousePos :: MonadIO m => m ImVec2 Source #
getMousePosOnOpeningCurrentPopup :: MonadIO m => m ImVec2 Source #
Retrieve mouse position at the time of opening popup we have beginPopup
into (helper to avoid user backing that value themselves).
isMouseDragging :: MonadIO m => ImGuiMouseButton -> CFloat -> m Bool Source #
getMouseDragDelta :: MonadIO m => ImGuiMouseButton -> CFloat -> m ImVec2 Source #
resetMouseDragDelta :: MonadIO m => ImGuiMouseButton -> m () Source #
wantCaptureKeyboard :: MonadIO m => m Bool Source #
shortcut :: MonadIO m => ImGuiKeyChord -> ImGuiInputFlags -> m Bool Source #
setNextItemShortcut :: MonadIO m => ImGuiKeyChord -> ImGuiInputFlags -> m () Source #
setItemDefaultFocus :: MonadIO m => m () Source #
Make last item the default focused item of a window.
setKeyboardFocusHere :: MonadIO m => CInt -> m () Source #
Focus keyboard on the next widget.
Use positive offset
to access sub components of a multiple component widget.
Use -1 to access previous widget.
setNextItemAllowOverlap :: MonadIO m => m () Source #
Allow next item to be overlapped by a subsequent item.
Useful with invisible buttons, selectable, treenode covering an area where subsequent items may need to be added.
Note that both selectable
and treeNode
have dedicated flags doing this.
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
.
ClipList helper for arbitrary unmaterialized ranges.
ClipRange a a |
Instances
(Ord a, Enum a, Num a) => ClipItems ClipRange a Source # | |
Show a => Show (ClipRange a) Source # | |
Eq a => Eq (ClipRange a) Source # | |
Ord a => Ord (ClipRange a) Source # | |
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.
getForegroundDrawList :: MonadIO m => m DrawList Source #
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.
framerate :: MonadIO m => m Float Source #
Estimate of application framerate (rolling average over 60 frames), in frame per second. Solely for convenience.
getTime :: MonadIO m => m Double Source #
Get global imgui time.
Incremented by io.DeltaTime every frame.
getFrameCount :: MonadIO m => m Int Source #
Get global imgui frame count.
Incremented by 1 every frame.
Types
class KnownNat (Count a) => FiniteEnum a where Source #
Nothing
newtype ImGuiWindowFlags Source #
Flags: for Begin(), BeginChild()
Flags for ImGui::Begin() (Those are per-window flags. There are shared flags in ImGuiIO: io.ConfigWindowsResizeFromEdges and io.ConfigWindowsMoveFromTitleBarOnly)
Instances
newtype ImGuiChildFlags Source #
Flags: for BeginChild()
Flags for ImGui::BeginChild() (Legacy: bit 0 must always correspond to ImGuiChildFlags_Border to be backward compatible with old API using 'bool border = false'. About using AutoResizeX/AutoResizeY flags: - May be combined with SetNextWindowSizeConstraints() to set a min/max size for each axis (see "Demo->Child->Auto-resize with Constraints"). - Size measurement for a given axis is only performed when the child window is within visible boundaries, or is just appearing. - This allows BeginChild() to return false when not within boundaries (e.g. when scrolling), which is more optimal. BUT it won't update its auto-size while clipped. While not perfect, it is a better default behavior as the always-on performance gain is more valuable than the occasional "resizing after becoming visible again" glitch. - You may also use ImGuiChildFlags_AlwaysAutoResize to force an update even when child window is not in view. HOWEVER PLEASE UNDERSTAND THAT DOING SO WILL PREVENT BeginChild() FROM EVER RETURNING FALSE, disabling benefits of coarse clipping.
Instances
newtype ImGuiInputTextFlags Source #
Flags: for InputText(), InputTextMultiline()
Flags for ImGui::InputText() (Those are per-item flags. There are shared flags in ImGuiIO: io.ConfigInputTextCursorBlink and io.ConfigInputTextEnterKeepActive)
Instances
newtype ImGuiTreeNodeFlags Source #
Flags: for TreeNode(), TreeNodeEx(), CollapsingHeader()
Flags for ImGui::TreeNodeEx(), ImGui::CollapsingHeader*()
Instances
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 instead of 'ImGuiPopupFlags flags', 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 use another flag, you need to pass in the ImGuiPopupFlags_MouseButtonRight flag explicitly. - Multiple buttons currently cannot be combined/or-ed in those functions (we could allow it later).
Instances
newtype ImGuiSelectableFlags Source #
Flags: for Selectable()
Flags for ImGui::Selectable()
Instances
newtype ImGuiComboFlags Source #
Flags: for BeginCombo()
Flags for ImGui::BeginCombo()
Instances
newtype ImGuiTabBarFlags Source #
Flags: for BeginTabBar()
Flags for ImGui::BeginTabBar()
Instances
newtype ImGuiTabItemFlags Source #
Flags: for BeginTabItem()
Flags for ImGui::BeginTabItem()
Instances
newtype ImGuiFocusedFlags Source #
Flags: for IsWindowFocused()
Flags for ImGui::IsWindowFocused()
Instances
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.
Instances
newtype ImGuiDragDropFlags Source #
Flags: for BeginDragDropSource(), AcceptDragDropPayload()
Flags for ImGui::BeginDragDropSource(), ImGui::AcceptDragDropPayload()
Instances
newtype ImGuiDataType Source #
Enum: A primary data type
A primary data type
Instances
Enum: A cardinal direction (Left, Right, Up, Down)
A cardinal direction
Instances
Storable ImGuiDir Source # | |
Show ImGuiDir Source # | |
Eq ImGuiDir Source # | |
Ord ImGuiDir Source # | |
Defined in DearImGui.Enums |
newtype ImGuiSortDirection Source #
Enum: A sorting direction (ascending or descending)
A sorting direction
Instances
Enum: A key identifier (ImGuiKey_XXX or ImGuiMod_XXX value)
A key identifier (ImGuiKey_XXX or ImGuiMod_XXX value): can represent Keyboard, Mouse and Gamepad values. All our named keys are >= 512. Keys value 0 to 511 are left unused as legacy native/opaque key values (< 1.87). Since >= 1.89 we increased typing (went from int to enum), some legacy code may need a cast to ImGuiKey. Read details about the 1.87 and 1.89 transition : https://github.com/ocornut/imgui/issues/4921 Note that Keys related to physical keys and are not the same concept as input Characters, the later are submitted via io.AddInputCharacter(). The keyboard key enum values are named after the keys on a standard US keyboard, and on other keyboard types the keys reported may not match the keycaps.
Instances
Storable ImGuiKey Source # | |
Show ImGuiKey Source # | |
Eq ImGuiKey Source # | |
Ord ImGuiKey Source # | |
Defined in DearImGui.Enums |
newtype ImGuiInputFlags Source #
Flags: for Shortcut(), SetNextItemShortcut()
Flags for Shortcut(), SetNextItemShortcut(), (and for upcoming extended versions of IsKeyPressed(), IsMouseClicked(), Shortcut(), SetKeyOwner(), SetItemKeyOwner() that are still in imgui_internal.h) Don't mistake with ImGuiInputTextFlags! (which is for ImGui::InputText() function)
Instances
newtype ImGuiConfigFlags Source #
Flags: for io.ConfigFlags
Configuration flags stored in io.ConfigFlags. Set by user/application.
Instances
newtype ImGuiBackendFlags Source #
Flags: for io.BackendFlags
Backend capabilities flags stored in io.BackendFlags. Set by imgui_impl_xxx or custom backend.
Instances
Enum: A color identifier for styling
Enumeration for PushStyleColor() / PopStyleColor()
Instances
Storable ImGuiCol Source # | |
Show ImGuiCol Source # | |
FiniteEnum ImGuiCol Source # | |
Eq ImGuiCol Source # | |
Ord ImGuiCol Source # | |
Defined in DearImGui.Enums | |
type Count ImGuiCol Source # | |
Defined in DearImGui.Enums |
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: CTRL+comma (Edit.GoToAll) can follow symbols inside comments, whereas CTRL+F12 (Edit.GoToImplementation) cannot. - In Visual Studio w/ Visual Assist installed: ALT+G (VAssistX.GoToImplementation) can also follow symbols inside comments. - In VS Code, CLion, etc.: CTRL+click can follow symbols inside 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.
Instances
newtype ImGuiButtonFlags Source #
Flags: for InvisibleButton()
Flags for InvisibleButton() [extended in imgui_internal.h]
Instances
newtype ImGuiColorEditFlags Source #
Flags: for ColorEdit4(), ColorPicker4() etc.
Flags for ColorEdit3() ColorEdit4() ColorPicker3() ColorPicker4() ColorButton()
Instances
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. (Those are per-item flags. There are shared flags in ImGuiIO: io.ConfigDragClickToInputText)
Instances
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.
Instances
newtype ImGuiMouseCursor Source #
Enum: A mouse cursor shape
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
Instances
newtype ImGuiMouseSource Source #
Enum; A mouse input source identifier (Mouse, TouchScreen, Pen)
Enumeration for AddMouseSourceEvent() actual source of Mouse Input data. Historically we use Mouse terminology everywhere to indicate pointer data, e.g. MousePos, IsMousePressed(), io.AddMousePosEvent() But that Mouse data can come from different source which occasionally may be useful for application to know about. You can submit a change of pointer type using io.AddMouseSourceEvent().
Instances
Enum: A condition for many Set*() functions
Enumeration for ImGui::SetNextWindow***(), SetWindow***(), 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.
Instances
Storable ImGuiCond Source # | |
Defined in DearImGui.Enums | |
Show ImGuiCond Source # | |
Eq ImGuiCond Source # | |
Ord ImGuiCond Source # | |
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 a 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.
Instances
newtype ImGuiTableColumnFlags Source #
Flags: For TableSetupColumn()
Flags for ImGui::TableSetupColumn()
Instances
newtype ImGuiTableRowFlags Source #
Flags: For TableNextRow()
Flags for ImGui::TableNextRow()
Instances
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 change 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.
Instances
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)
Instances
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.
Instances
newtype ImFontAtlasFlags Source #
Flags: for ImFontAtlas build
Flags for ImFontAtlas build
Instances
pattern ImFontAtlasFlags_NoBakedLines :: ImFontAtlasFlags Source #
Don't build thick line textures into the atlas (save a little texture memory, allow support for pointnearest filtering). The AntiAliasedLinesUseTex features uses them, otherwise they will be rendered using polygons (more expensive for CPUGPU).
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 ImFontAtlasFlags_None :: ImFontAtlasFlags Source #
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 linesborders using textures when possible. Require backend to render with bilinear filtering (NOT pointnearest 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 ImDrawListFlags_None :: ImDrawListFlags Source #
pattern ImDrawFlags_RoundCornersMask_ :: ImDrawFlags Source #
pattern ImDrawFlags_RoundCornersDefault_ :: ImDrawFlags Source #
Default to ALL corners if none of the _RoundCornersXX flags are specified.
pattern ImDrawFlags_RoundCornersAll :: ImDrawFlags Source #
pattern ImDrawFlags_RoundCornersRight :: ImDrawFlags Source #
pattern ImDrawFlags_RoundCornersLeft :: ImDrawFlags Source #
pattern ImDrawFlags_RoundCornersBottom :: ImDrawFlags Source #
pattern ImDrawFlags_RoundCornersTop :: ImDrawFlags Source #
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 ImDrawFlags_None :: ImDrawFlags Source #
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 ImGuiTableBgTarget_None :: ImGuiTableBgTarget Source #
pattern ImGuiTableRowFlags_Headers :: ImGuiTableRowFlags Source #
Identify header row (set default background color + width of its contents accounted differently for auto column width)
pattern ImGuiTableRowFlags_None :: ImGuiTableRowFlags Source #
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_AngledHeader :: ImGuiTableColumnFlags Source #
TableHeadersRow() will submit an angled header row for this column. Note this will add an extra row.
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 horizontal label for this column. Convenient for some small columns. Name will still appear in context menu or in angled headers.
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_NoResize :: ImGuiTableColumnFlags Source #
Disable manual resizing.
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 ImGuiTableColumnFlags_None :: ImGuiTableColumnFlags Source #
pattern ImGuiTableFlags_SizingMask_ :: ImGuiTableFlags Source #
pattern ImGuiTableFlags_HighlightHoveredColumn :: ImGuiTableFlags Source #
Highlight column headers when hovered (may evolve into a fuller highlight)
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 creates 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 outermost padding.
pattern ImGuiTableFlags_PadOuterX :: ImGuiTableFlags Source #
Default if BordersOuterV is on. Enable outermost 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 appear in Headers). -> May move to style
pattern ImGuiTableFlags_NoBordersInBody :: ImGuiTableFlags Source #
- ALPHA
- Disable vertical borders in columns Body (borders will always appear in Headers). -> May move to style
pattern ImGuiTableFlags_Borders :: ImGuiTableFlags Source #
Draw all borders.
pattern ImGuiTableFlags_BordersOuter :: ImGuiTableFlags Source #
Draw outer borders.
pattern ImGuiTableFlags_BordersInner :: ImGuiTableFlags Source #
Draw inner 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 ImGuiTableFlags_None :: ImGuiTableFlags Source #
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), same as _None
pattern ImGuiCond_None :: ImGuiCond Source #
No condition (always set the variable), same as _Always
pattern ImGuiMouseSource_COUNT :: ImGuiMouseSource Source #
pattern ImGuiMouseSource_Pen :: ImGuiMouseSource Source #
Input is coming from a pressure/magnetic pen (often used in conjunction with high-sampling rates).
pattern ImGuiMouseSource_TouchScreen :: ImGuiMouseSource Source #
Input is coming from a touch screen (no hovering prior to initial press, less precise initial press aiming, dual-axis wheeling possible).
pattern ImGuiMouseSource_Mouse :: ImGuiMouseSource Source #
Input is coming from an actual mouse.
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 a horizontal border
pattern ImGuiMouseCursor_ResizeAll :: ImGuiMouseCursor Source #
(Unused by Dear ImGui functions)
pattern ImGuiMouseCursor_TextInput :: ImGuiMouseCursor Source #
When hovering over InputText, etc.
pattern ImGuiMouseCursor_Arrow :: ImGuiMouseCursor Source #
pattern ImGuiMouseCursor_None :: ImGuiMouseCursor Source #
pattern ImGuiMouseButton_Middle :: ImGuiMouseButton Source #
pattern ImGuiMouseButton_Right :: ImGuiMouseButton Source #
pattern ImGuiMouseButton_Left :: ImGuiMouseButton Source #
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_WrapAround :: ImGuiSliderFlags Source #
Enable wrapping around from max to min and from min to max (only supported by DragXXX() functions for now.
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 ImGuiSliderFlags_None :: ImGuiSliderFlags Source #
pattern ImGuiColorEditFlags_InputMask_ :: ImGuiColorEditFlags Source #
Obsolete names
pattern ImGuiColorEditFlags_DefaultOptions_ :: ImGuiColorEditFlags Source #
- Internal
- Masks
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_DisplayHex :: ImGuiColorEditFlags Source #
- Display
- // "
pattern ImGuiColorEditFlags_DisplayHSV :: ImGuiColorEditFlags Source #
- Display
- // "
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 ImGuiColorEditFlags_None :: ImGuiColorEditFlags Source #
pattern ImGuiButtonFlags_MouseButtonMask_ :: ImGuiButtonFlags Source #
- Internal
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 ImGuiButtonFlags_None :: ImGuiButtonFlags Source #
pattern ImGuiStyleVar_SeparatorTextPadding :: ImGuiStyleVar Source #
ImVec2 SeparatorTextPadding
pattern ImGuiStyleVar_SeparatorTextAlign :: ImGuiStyleVar Source #
ImVec2 SeparatorTextAlign
pattern ImGuiStyleVar_SeparatorTextBorderSize :: ImGuiStyleVar Source #
float SeparatorTextBorderSize
pattern ImGuiStyleVar_SelectableTextAlign :: ImGuiStyleVar Source #
ImVec2 SelectableTextAlign
pattern ImGuiStyleVar_ButtonTextAlign :: ImGuiStyleVar Source #
ImVec2 ButtonTextAlign
pattern ImGuiStyleVar_TableAngledHeadersTextAlign :: ImGuiStyleVar Source #
ImVec2 TableAngledHeadersTextAlign
pattern ImGuiStyleVar_TableAngledHeadersAngle :: ImGuiStyleVar Source #
float TableAngledHeadersAngle
pattern ImGuiStyleVar_TabBarBorderSize :: ImGuiStyleVar Source #
float TabBarBorderSize
pattern ImGuiStyleVar_TabBorderSize :: ImGuiStyleVar Source #
float TabBorderSize
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 ImGuiStyleVar_Alpha :: ImGuiStyleVar Source #
float Alpha
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_DragDropTarget :: ImGuiCol Source #
Rectangle highlighting a drop target
pattern ImGuiCol_TextSelectedBg :: ImGuiCol Source #
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_PlotHistogramHovered :: ImGuiCol Source #
pattern ImGuiCol_PlotHistogram :: ImGuiCol Source #
pattern ImGuiCol_PlotLinesHovered :: ImGuiCol Source #
pattern ImGuiCol_PlotLines :: ImGuiCol Source #
pattern ImGuiCol_TabDimmedSelectedOverline :: ImGuiCol Source #
..horizontal overline, when tab-bar is unfocused & tab is selected
pattern ImGuiCol_TabDimmedSelected :: ImGuiCol Source #
Tab background, when tab-bar is unfocused & tab is selected
pattern ImGuiCol_TabDimmed :: ImGuiCol Source #
Tab background, when tab-bar is unfocused & tab is unselected
pattern ImGuiCol_TabSelectedOverline :: ImGuiCol Source #
Tab horizontal overline, when tab-bar is focused & tab is selected
pattern ImGuiCol_TabSelected :: ImGuiCol Source #
Tab background, when tab-bar is focused & tab is selected
pattern ImGuiCol_Tab :: ImGuiCol Source #
Tab background, when tab-bar is focused & tab is unselected
pattern ImGuiCol_TabHovered :: ImGuiCol Source #
Tab background, when hovered
pattern ImGuiCol_ResizeGripActive :: ImGuiCol Source #
pattern ImGuiCol_ResizeGripHovered :: ImGuiCol Source #
pattern ImGuiCol_ResizeGrip :: ImGuiCol Source #
Resize grip in lower-right and lower-left corners of windows.
pattern ImGuiCol_SeparatorActive :: ImGuiCol Source #
pattern ImGuiCol_SeparatorHovered :: ImGuiCol Source #
pattern ImGuiCol_Separator :: ImGuiCol Source #
pattern ImGuiCol_HeaderActive :: ImGuiCol Source #
pattern ImGuiCol_HeaderHovered :: ImGuiCol Source #
pattern ImGuiCol_Header :: ImGuiCol Source #
Header* colors are used for CollapsingHeader, TreeNode, Selectable, MenuItem
pattern ImGuiCol_ButtonActive :: ImGuiCol Source #
pattern ImGuiCol_ButtonHovered :: ImGuiCol Source #
pattern ImGuiCol_Button :: ImGuiCol Source #
pattern ImGuiCol_SliderGrabActive :: ImGuiCol Source #
pattern ImGuiCol_SliderGrab :: ImGuiCol Source #
pattern ImGuiCol_CheckMark :: ImGuiCol Source #
Checkbox tick and RadioButton circle
pattern ImGuiCol_ScrollbarGrabActive :: ImGuiCol Source #
pattern ImGuiCol_ScrollbarGrabHovered :: ImGuiCol Source #
pattern ImGuiCol_ScrollbarGrab :: ImGuiCol Source #
pattern ImGuiCol_ScrollbarBg :: ImGuiCol Source #
pattern ImGuiCol_MenuBarBg :: ImGuiCol Source #
pattern ImGuiCol_TitleBgCollapsed :: ImGuiCol Source #
Title bar when collapsed
pattern ImGuiCol_TitleBgActive :: ImGuiCol Source #
Title bar when focused
pattern ImGuiCol_TitleBg :: ImGuiCol Source #
Title bar
pattern ImGuiCol_FrameBgActive :: ImGuiCol Source #
pattern ImGuiCol_FrameBgHovered :: ImGuiCol Source #
pattern ImGuiCol_FrameBg :: ImGuiCol Source #
Background of checkbox, radio button, plot, slider, text input
pattern ImGuiCol_BorderShadow :: ImGuiCol Source #
pattern ImGuiCol_Border :: ImGuiCol Source #
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 ImGuiCol_TextDisabled :: ImGuiCol Source #
pattern ImGuiCol_Text :: ImGuiCol Source #
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 ImGuiBackendFlags_None :: ImGuiBackendFlags Source #
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_NoKeyboard :: ImGuiConfigFlags Source #
Instruct dear imgui to disable keyboard inputs and interactions. This is done by ignoring keyboard events and clearing existing states.
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 dear imgui to disable mouse inputs and interactions.
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. Backend also needs to set ImGuiBackendFlags_HasGamepad.
pattern ImGuiConfigFlags_NavEnableKeyboard :: ImGuiConfigFlags Source #
Master keyboard navigation enable flag. Enable full Tabbing + directional arrows + space/enter to activate.
pattern ImGuiConfigFlags_None :: ImGuiConfigFlags Source #
pattern ImGuiInputFlags_Tooltip :: ImGuiInputFlags Source #
Automatically display a tooltip when hovering item [BETA] Unsure of right api (opt-in/opt-out)
pattern ImGuiInputFlags_RouteFromRootWindow :: ImGuiInputFlags Source #
Option: route evaluated from the point of view of root window rather than current window.
pattern ImGuiInputFlags_RouteUnlessBgFocused :: ImGuiInputFlags Source #
Option: global route: will not be applied if underlying background/void is focused (== no Dear ImGui windows are focused). Useful for overlay applications.
pattern ImGuiInputFlags_RouteOverActive :: ImGuiInputFlags Source #
Option: global route: higher priority than active item. Unlikely you need to use that: will interfere with every active items, e.g. CTRL+A registered by InputText will be overridden by this. May not be fully honored as user/internal code is likely to always assume they can access keys when active.
pattern ImGuiInputFlags_RouteOverFocused :: ImGuiInputFlags Source #
Option: global route: higher priority than focused route (unless active item in focused route).
pattern ImGuiInputFlags_RouteAlways :: ImGuiInputFlags Source #
Do not register route, poll keys directly.
pattern ImGuiInputFlags_RouteGlobal :: ImGuiInputFlags Source #
Global route (unless a focused window or active item registered the route).
pattern ImGuiInputFlags_RouteFocused :: ImGuiInputFlags Source #
Route to windows in the focus stack (DEFAULT). Deep-most focused window takes inputs. Active item takes inputs over deep-most focused window.
pattern ImGuiInputFlags_RouteActive :: ImGuiInputFlags Source #
Route to active item only.
pattern ImGuiInputFlags_Repeat :: ImGuiInputFlags Source #
Enable repeat. Return true on successive repeats. Default for legacy IsKeyPressed(). NOT Default for legacy IsMouseClicked(). MUST BE == 1.
pattern ImGuiInputFlags_None :: ImGuiInputFlags Source #
pattern ImGuiKey_NamedKey_COUNT :: ImGuiKey Source #
pattern ImGuiKey_NamedKey_END :: ImGuiKey Source #
pattern ImGuiKey_NamedKey_BEGIN :: ImGuiKey Source #
pattern ImGuiMod_Mask_ :: ImGuiKey Source #
4-bits
pattern ImGuiMod_Super :: ImGuiKey Source #
Windows/Super (non-macOS), Ctrl (macOS)
pattern ImGuiMod_Alt :: ImGuiKey Source #
Option/Menu
pattern ImGuiMod_Shift :: ImGuiKey Source #
Shift
pattern ImGuiMod_Ctrl :: ImGuiKey Source #
Ctrl (non-macOS), Cmd (macOS)
pattern ImGuiMod_None :: ImGuiKey Source #
pattern ImGuiKey_COUNT :: ImGuiKey Source #
Keyboard Modifiers (explicitly submitted by backend via AddKeyEvent() calls)
pattern ImGuiKey_ReservedForModSuper :: ImGuiKey Source #
pattern ImGuiKey_ReservedForModAlt :: ImGuiKey Source #
pattern ImGuiKey_ReservedForModShift :: ImGuiKey Source #
pattern ImGuiKey_ReservedForModCtrl :: ImGuiKey Source #
pattern ImGuiKey_MouseWheelY :: ImGuiKey Source #
- Internal
- Reserved for mod storage
pattern ImGuiKey_MouseWheelX :: ImGuiKey Source #
pattern ImGuiKey_MouseX2 :: ImGuiKey Source #
pattern ImGuiKey_MouseX1 :: ImGuiKey Source #
pattern ImGuiKey_MouseMiddle :: ImGuiKey Source #
pattern ImGuiKey_MouseRight :: ImGuiKey Source #
pattern ImGuiKey_MouseLeft :: ImGuiKey Source #
pattern ImGuiKey_GamepadRStickDown :: ImGuiKey Source #
- Analog
pattern ImGuiKey_GamepadRStickUp :: ImGuiKey Source #
- Analog
pattern ImGuiKey_GamepadRStickRight :: ImGuiKey Source #
- Analog
pattern ImGuiKey_GamepadRStickLeft :: ImGuiKey Source #
- Analog
pattern ImGuiKey_GamepadLStickDown :: ImGuiKey Source #
- Analog
- // Move Window (in Windowing mode)
pattern ImGuiKey_GamepadLStickUp :: ImGuiKey Source #
- Analog
- // Move Window (in Windowing mode)
pattern ImGuiKey_GamepadLStickRight :: ImGuiKey Source #
- Analog
- // Move Window (in Windowing mode)
pattern ImGuiKey_GamepadLStickLeft :: ImGuiKey Source #
- Analog
- // Move Window (in Windowing mode)
pattern ImGuiKey_GamepadR3 :: ImGuiKey Source #
R Stick (Xbox) R3 (Switch) R3 (PS)
pattern ImGuiKey_GamepadL3 :: ImGuiKey Source #
L Stick (Xbox) L3 (Switch) L3 (PS)
pattern ImGuiKey_GamepadR2 :: ImGuiKey Source #
R Trig. (Xbox) ZR (Switch) R2 (PS) [Analog]
pattern ImGuiKey_GamepadL2 :: ImGuiKey Source #
L Trig. (Xbox) ZL (Switch) L2 (PS) [Analog]
pattern ImGuiKey_GamepadR1 :: ImGuiKey Source #
R Bumper (Xbox) R (Switch) R1 (PS) / Tweak Faster Focus Next (in Windowing mode)
pattern ImGuiKey_GamepadL1 :: ImGuiKey Source #
L Bumper (Xbox) L (Switch) L1 (PS) / Tweak Slower Focus Previous (in Windowing mode)
pattern ImGuiKey_GamepadDpadDown :: ImGuiKey Source #
D-pad Down / Move Tweak / Resize Window (in Windowing mode)
pattern ImGuiKey_GamepadDpadUp :: ImGuiKey Source #
D-pad Up / Move Tweak / Resize Window (in Windowing mode)
pattern ImGuiKey_GamepadDpadRight :: ImGuiKey Source #
D-pad Right / Move Tweak / Resize Window (in Windowing mode)
pattern ImGuiKey_GamepadDpadLeft :: ImGuiKey Source #
D-pad Left / Move Tweak / Resize Window (in Windowing mode)
pattern ImGuiKey_GamepadFaceDown :: ImGuiKey Source #
A (Xbox) B (Switch) Cross (PS) / Activate Open Toggle Tweak
pattern ImGuiKey_GamepadFaceUp :: ImGuiKey Source #
Y (Xbox) X (Switch) Triangle (PS) / Text Input On-screen Keyboard
pattern ImGuiKey_GamepadFaceRight :: ImGuiKey Source #
B (Xbox) A (Switch) Circle (PS) / Cancel Close / Exit
pattern ImGuiKey_GamepadFaceLeft :: ImGuiKey Source #
X (Xbox) Y (Switch) Square (PS) / Tap: Toggle Menu. Hold: Windowing mode (FocusMove/Resize windows)
pattern ImGuiKey_GamepadBack :: ImGuiKey Source #
View (Xbox) - (Switch) Share (PS)
pattern ImGuiKey_GamepadStart :: ImGuiKey Source #
Menu (Xbox) + (Switch) Start/Options (PS)
pattern ImGuiKey_AppForward :: ImGuiKey Source #
Gamepad (some of those are analog values, 0.0f to 1.0f) // NAVIGATION ACTION
pattern ImGuiKey_AppBack :: ImGuiKey Source #
Available on some keyboard/mouses. Often referred as "Browser Back"
pattern ImGuiKey_KeypadEqual :: ImGuiKey Source #
pattern ImGuiKey_KeypadEnter :: ImGuiKey Source #
pattern ImGuiKey_KeypadAdd :: ImGuiKey Source #
pattern ImGuiKey_KeypadSubtract :: ImGuiKey Source #
pattern ImGuiKey_KeypadMultiply :: ImGuiKey Source #
pattern ImGuiKey_KeypadDivide :: ImGuiKey Source #
pattern ImGuiKey_KeypadDecimal :: ImGuiKey Source #
pattern ImGuiKey_Keypad9 :: ImGuiKey Source #
pattern ImGuiKey_Keypad8 :: ImGuiKey Source #
pattern ImGuiKey_Keypad7 :: ImGuiKey Source #
pattern ImGuiKey_Keypad6 :: ImGuiKey Source #
pattern ImGuiKey_Keypad5 :: ImGuiKey Source #
pattern ImGuiKey_Keypad4 :: ImGuiKey Source #
pattern ImGuiKey_Keypad3 :: ImGuiKey Source #
pattern ImGuiKey_Keypad2 :: ImGuiKey Source #
pattern ImGuiKey_Keypad1 :: ImGuiKey Source #
pattern ImGuiKey_Keypad0 :: ImGuiKey Source #
pattern ImGuiKey_Pause :: ImGuiKey Source #
pattern ImGuiKey_PrintScreen :: ImGuiKey Source #
pattern ImGuiKey_NumLock :: ImGuiKey Source #
pattern ImGuiKey_ScrollLock :: ImGuiKey Source #
pattern ImGuiKey_CapsLock :: ImGuiKey Source #
pattern ImGuiKey_GraveAccent :: ImGuiKey Source #
`
pattern ImGuiKey_RightBracket :: ImGuiKey Source #
]
pattern ImGuiKey_Backslash :: ImGuiKey Source #
(this text inhibit multiline comment caused by backslash)
pattern ImGuiKey_LeftBracket :: ImGuiKey Source #
[
pattern ImGuiKey_Equal :: ImGuiKey Source #
=
pattern ImGuiKey_Semicolon :: ImGuiKey Source #
;
pattern ImGuiKey_Slash :: ImGuiKey Source #
/
pattern ImGuiKey_Period :: ImGuiKey Source #
.
pattern ImGuiKey_Minus :: ImGuiKey Source #
pattern ImGuiKey_Comma :: ImGuiKey Source #
,
pattern ImGuiKey_Apostrophe :: ImGuiKey Source #
'
pattern ImGuiKey_F24 :: ImGuiKey Source #
pattern ImGuiKey_F23 :: ImGuiKey Source #
pattern ImGuiKey_F22 :: ImGuiKey Source #
pattern ImGuiKey_F21 :: ImGuiKey Source #
pattern ImGuiKey_F20 :: ImGuiKey Source #
pattern ImGuiKey_F19 :: ImGuiKey Source #
pattern ImGuiKey_F18 :: ImGuiKey Source #
pattern ImGuiKey_F17 :: ImGuiKey Source #
pattern ImGuiKey_F16 :: ImGuiKey Source #
pattern ImGuiKey_F15 :: ImGuiKey Source #
pattern ImGuiKey_F14 :: ImGuiKey Source #
pattern ImGuiKey_F13 :: ImGuiKey Source #
pattern ImGuiKey_F12 :: ImGuiKey Source #
pattern ImGuiKey_F11 :: ImGuiKey Source #
pattern ImGuiKey_F10 :: ImGuiKey Source #
pattern ImGuiKey_F9 :: ImGuiKey Source #
pattern ImGuiKey_F8 :: ImGuiKey Source #
pattern ImGuiKey_F7 :: ImGuiKey Source #
pattern ImGuiKey_F6 :: ImGuiKey Source #
pattern ImGuiKey_F5 :: ImGuiKey Source #
pattern ImGuiKey_F4 :: ImGuiKey Source #
pattern ImGuiKey_F3 :: ImGuiKey Source #
pattern ImGuiKey_F2 :: ImGuiKey Source #
pattern ImGuiKey_F1 :: ImGuiKey Source #
pattern ImGuiKey_Z :: ImGuiKey Source #
pattern ImGuiKey_Y :: ImGuiKey Source #
pattern ImGuiKey_X :: ImGuiKey Source #
pattern ImGuiKey_W :: ImGuiKey Source #
pattern ImGuiKey_V :: ImGuiKey Source #
pattern ImGuiKey_U :: ImGuiKey Source #
pattern ImGuiKey_T :: ImGuiKey Source #
pattern ImGuiKey_S :: ImGuiKey Source #
pattern ImGuiKey_R :: ImGuiKey Source #
pattern ImGuiKey_Q :: ImGuiKey Source #
pattern ImGuiKey_P :: ImGuiKey Source #
pattern ImGuiKey_O :: ImGuiKey Source #
pattern ImGuiKey_N :: ImGuiKey Source #
pattern ImGuiKey_M :: ImGuiKey Source #
pattern ImGuiKey_L :: ImGuiKey Source #
pattern ImGuiKey_K :: ImGuiKey Source #
pattern ImGuiKey_J :: ImGuiKey Source #
pattern ImGuiKey_I :: ImGuiKey Source #
pattern ImGuiKey_H :: ImGuiKey Source #
pattern ImGuiKey_G :: ImGuiKey Source #
pattern ImGuiKey_F :: ImGuiKey Source #
pattern ImGuiKey_E :: ImGuiKey Source #
pattern ImGuiKey_D :: ImGuiKey Source #
pattern ImGuiKey_C :: ImGuiKey Source #
pattern ImGuiKey_B :: ImGuiKey Source #
pattern ImGuiKey_A :: ImGuiKey Source #
pattern ImGuiKey_9 :: ImGuiKey Source #
pattern ImGuiKey_8 :: ImGuiKey Source #
pattern ImGuiKey_7 :: ImGuiKey Source #
pattern ImGuiKey_6 :: ImGuiKey Source #
pattern ImGuiKey_5 :: ImGuiKey Source #
pattern ImGuiKey_4 :: ImGuiKey Source #
pattern ImGuiKey_3 :: ImGuiKey Source #
pattern ImGuiKey_2 :: ImGuiKey Source #
pattern ImGuiKey_1 :: ImGuiKey Source #
pattern ImGuiKey_0 :: ImGuiKey Source #
pattern ImGuiKey_Menu :: ImGuiKey Source #
pattern ImGuiKey_RightSuper :: ImGuiKey Source #
pattern ImGuiKey_RightAlt :: ImGuiKey Source #
pattern ImGuiKey_RightShift :: ImGuiKey Source #
pattern ImGuiKey_RightCtrl :: ImGuiKey Source #
pattern ImGuiKey_LeftSuper :: ImGuiKey Source #
pattern ImGuiKey_LeftAlt :: ImGuiKey Source #
pattern ImGuiKey_LeftShift :: ImGuiKey Source #
pattern ImGuiKey_LeftCtrl :: ImGuiKey Source #
pattern ImGuiKey_Escape :: ImGuiKey Source #
pattern ImGuiKey_Enter :: ImGuiKey Source #
pattern ImGuiKey_Space :: ImGuiKey Source #
pattern ImGuiKey_Backspace :: ImGuiKey Source #
pattern ImGuiKey_Delete :: ImGuiKey Source #
pattern ImGuiKey_Insert :: ImGuiKey Source #
pattern ImGuiKey_End :: ImGuiKey Source #
pattern ImGuiKey_Home :: ImGuiKey Source #
pattern ImGuiKey_PageDown :: ImGuiKey Source #
pattern ImGuiKey_PageUp :: ImGuiKey Source #
pattern ImGuiKey_DownArrow :: ImGuiKey Source #
pattern ImGuiKey_UpArrow :: ImGuiKey Source #
pattern ImGuiKey_RightArrow :: ImGuiKey Source #
pattern ImGuiKey_LeftArrow :: ImGuiKey Source #
pattern ImGuiKey_Tab :: ImGuiKey Source #
ImGuiKey_NamedKey_BEGIN
pattern ImGuiKey_None :: ImGuiKey Source #
pattern ImGuiSortDirection_Descending :: ImGuiSortDirection Source #
Descending = 9->0, Z->A etc.
pattern ImGuiSortDirection_Ascending :: ImGuiSortDirection Source #
Ascending = 0->9, A->Z etc.
pattern ImGuiSortDirection_None :: ImGuiSortDirection Source #
pattern ImGuiDir_COUNT :: ImGuiDir Source #
pattern ImGuiDir_Down :: ImGuiDir Source #
pattern ImGuiDir_Up :: ImGuiDir Source #
pattern ImGuiDir_Right :: ImGuiDir Source #
pattern ImGuiDir_Left :: ImGuiDir Source #
pattern ImGuiDir_None :: ImGuiDir Source #
pattern ImGuiDataType_Double :: ImGuiDataType Source #
double
pattern ImGuiDataType_Float :: ImGuiDataType Source #
float
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_S32 :: ImGuiDataType Source #
int
pattern ImGuiDataType_U16 :: ImGuiDataType Source #
unsigned short
pattern ImGuiDataType_S16 :: ImGuiDataType Source #
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_PayloadNoCrossProcess :: ImGuiDragDropFlags Source #
Hint to specify that the payload may not be copied outside current process.
pattern ImGuiDragDropFlags_PayloadNoCrossContext :: ImGuiDragDropFlags Source #
Hint to specify that the payload may not be copied outside current dear imgui context.
pattern ImGuiDragDropFlags_PayloadAutoExpire :: 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 disables this behavior so you can still call IsItemHovered() on the source item.
pattern ImGuiDragDropFlags_SourceNoPreviewTooltip :: ImGuiDragDropFlags Source #
Disable preview tooltip. By default, a successful call to BeginDragDropSource opens a tooltip so you can display a preview or description of the source contents. This flag disables this behavior.
pattern ImGuiDragDropFlags_None :: ImGuiDragDropFlags Source #
BeginDragDropSource() flags
pattern ImGuiHoveredFlags_NoSharedDelay :: ImGuiHoveredFlags Source #
IsItemHovered() only: Disable shared delay system where moving from one item to the next keeps the previous timer for a short time (standard for tooltips with long delays)
pattern ImGuiHoveredFlags_DelayNormal :: ImGuiHoveredFlags Source #
IsItemHovered() only: Return true after style.HoverDelayNormal elapsed (~0.40 sec) (shared between items) + requires mouse to be stationary for style.HoverStationaryDelay (once per item).
pattern ImGuiHoveredFlags_DelayShort :: ImGuiHoveredFlags Source #
IsItemHovered() only: Return true after style.HoverDelayShort elapsed (~0.15 sec) (shared between items) + requires mouse to be stationary for style.HoverStationaryDelay (once per item).
pattern ImGuiHoveredFlags_DelayNone :: ImGuiHoveredFlags Source #
IsItemHovered() only: Return true immediately (default). As this is the default you generally ignore this.
pattern ImGuiHoveredFlags_Stationary :: ImGuiHoveredFlags Source #
Require mouse to be stationary for style.HoverStationaryDelay (~0.15 sec) _at least one time_. After this, can move on same item/window. Using the stationary test tends to reduces the need for a long delay.
pattern ImGuiHoveredFlags_ForTooltip :: ImGuiHoveredFlags Source #
Shortcut for standard flags when using IsItemHovered() + SetTooltip() sequence.
pattern ImGuiHoveredFlags_RootAndChildWindows :: ImGuiHoveredFlags Source #
Tooltips mode
pattern ImGuiHoveredFlags_RectOnly :: ImGuiHoveredFlags Source #
pattern ImGuiHoveredFlags_NoNavOverride :: ImGuiHoveredFlags Source #
IsItemHovered() only: Disable using gamepad/keyboard navigation state when active, always query mouse
pattern ImGuiHoveredFlags_AllowWhenDisabled :: ImGuiHoveredFlags Source #
IsItemHovered() only: Return true even if the item is disabled
pattern ImGuiHoveredFlags_AllowWhenOverlappedByWindow :: ImGuiHoveredFlags Source #
IsItemHovered() only: Return true even if the position is obstructed or overlapped by another window.
pattern ImGuiHoveredFlags_AllowWhenOverlappedByItem :: ImGuiHoveredFlags Source #
IsItemHovered() only: Return true even if the item uses AllowOverlap mode and is overlapped by another hoverable item.
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 ImGuiFocusedFlags_None :: ImGuiFocusedFlags Source #
pattern ImGuiTabItemFlags_NoAssumedClosure :: ImGuiTabItemFlags Source #
Tab is selected when trying to close + closure is not immediately 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 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()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 may handle this behavior manually 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 + set ImGuiTabItemFlags_NoAssumedClosure.
pattern ImGuiTabItemFlags_None :: ImGuiTabItemFlags Source #
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_DrawSelectedOverline :: ImGuiTabBarFlags Source #
Draw selected overline markers over selected tab
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 may handle this behavior manually 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 ImGuiTabBarFlags_None :: ImGuiTabBarFlags Source #
pattern ImGuiComboFlags_HeightMask_ :: ImGuiComboFlags Source #
pattern ImGuiComboFlags_WidthFitPreview :: ImGuiComboFlags Source #
Width dynamically calculated from preview contents
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 ImGuiComboFlags_None :: ImGuiComboFlags Source #
pattern ImGuiSelectableFlags_AllowOverlap :: 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 #
Frame will span all columns of its container table (text will still fit in current column)
pattern ImGuiSelectableFlags_DontClosePopups :: ImGuiSelectableFlags Source #
Clicking this doesn't close parent popup window
pattern ImGuiSelectableFlags_None :: ImGuiSelectableFlags Source #
pattern ImGuiPopupFlags_AnyPopup :: ImGuiPopupFlags Source #
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_NoReopen :: ImGuiPopupFlags Source #
For OpenPopup*(), BeginPopupContext*(): don't reopen same popup if already open (won't reposition, won't reinitialize navigation)
pattern ImGuiPopupFlags_MouseButtonMask_ :: ImGuiPopupFlags Source #
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 ImGuiPopupFlags_None :: ImGuiPopupFlags Source #
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_SpanAllColumns :: ImGuiTreeNodeFlags Source #
Frame will span all columns of its container table (text will still fit in current column)
pattern ImGuiTreeNodeFlags_SpanTextWidth :: ImGuiTreeNodeFlags Source #
Narrow hit box + narrow hovering highlight, will only cover the label text.
pattern ImGuiTreeNodeFlags_SpanFullWidth :: ImGuiTreeNodeFlags Source #
Extend hit box to the left-most and right-most edges (cover the indent 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 without using AllowOverlap mode.
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() before the node.
pattern ImGuiTreeNodeFlags_Bullet :: ImGuiTreeNodeFlags Source #
Display a bullet instead of arrow. IMPORTANT: node can still be marked open/close if you don't set the _Leaf flag!
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_AllowOverlap :: 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 ImGuiTreeNodeFlags_Selected :: ImGuiTreeNodeFlags Source #
Draw as selected
pattern ImGuiTreeNodeFlags_None :: ImGuiTreeNodeFlags Source #
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_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_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_NoHorizontalScroll :: ImGuiInputTextFlags Source #
Disable following the cursor horizontally
pattern ImGuiInputTextFlags_DisplayEmptyRefVal :: ImGuiInputTextFlags Source #
InputFloat(), InputInt(), InputScalar() etc. only: when value is zero, do not display it. Generally used with ImGuiInputTextFlags_ParseEmptyRefVal.
pattern ImGuiInputTextFlags_ParseEmptyRefVal :: ImGuiInputTextFlags Source #
InputFloat(), InputInt(), InputScalar() etc. only: parse empty string as zero value.
pattern ImGuiInputTextFlags_AutoSelectAll :: ImGuiInputTextFlags Source #
Select entire text when first taking mouse focus
pattern ImGuiInputTextFlags_AlwaysOverwrite :: ImGuiInputTextFlags Source #
Overwrite mode
pattern ImGuiInputTextFlags_Password :: ImGuiInputTextFlags Source #
Password mode, display all characters as *
, disable copy
pattern ImGuiInputTextFlags_ReadOnly :: ImGuiInputTextFlags Source #
Read-only mode
pattern ImGuiInputTextFlags_CtrlEnterForNewLine :: ImGuiInputTextFlags Source #
In multi-line mode, validate with Enter, add new line with Ctrl+Enter (default is opposite: validate with Ctrl+Enter, add line with Enter).
pattern ImGuiInputTextFlags_EscapeClearsAll :: ImGuiInputTextFlags Source #
Escape key clears content if not empty, and deactivate otherwise (contrast to default behavior of Escape to revert)
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_AllowTabInput :: ImGuiInputTextFlags Source #
Pressing TAB input a 't' character into the text field
pattern ImGuiInputTextFlags_CharsNoBlank :: ImGuiInputTextFlags Source #
Filter out spaces, tabs
pattern ImGuiInputTextFlags_CharsUppercase :: ImGuiInputTextFlags Source #
Turn a..z into A..Z
pattern ImGuiInputTextFlags_CharsScientific :: ImGuiInputTextFlags Source #
Allow 0123456789.+-*/eE (Scientific notation input)
pattern ImGuiInputTextFlags_CharsHexadecimal :: ImGuiInputTextFlags Source #
Allow 0123456789ABCDEFabcdef
pattern ImGuiInputTextFlags_CharsDecimal :: ImGuiInputTextFlags Source #
Allow 0123456789.+-*/
pattern ImGuiInputTextFlags_None :: ImGuiInputTextFlags Source #
pattern ImGuiChildFlags_NavFlattened :: ImGuiChildFlags Source #
Share focus scope, allow gamepad/keyboard navigation to cross over parent border to this child or between sibling child windows.
pattern ImGuiChildFlags_FrameStyle :: ImGuiChildFlags Source #
Style the child window like a framed item: use FrameBg, FrameRounding, FrameBorderSize, FramePadding instead of ChildBg, ChildRounding, ChildBorderSize, WindowPadding.
pattern ImGuiChildFlags_AlwaysAutoResize :: ImGuiChildFlags Source #
Combined with AutoResizeX/AutoResizeY. Always measure size even when child is hidden, always return true, always disable clipping optimization! NOT RECOMMENDED.
pattern ImGuiChildFlags_AutoResizeY :: ImGuiChildFlags Source #
Enable auto-resizing height. Read "IMPORTANT: Size measurement" details above.
pattern ImGuiChildFlags_AutoResizeX :: ImGuiChildFlags Source #
Enable auto-resizing width. Read "IMPORTANT: Size measurement" details above.
pattern ImGuiChildFlags_ResizeY :: ImGuiChildFlags Source #
Allow resize from bottom border (layout direction). "
pattern ImGuiChildFlags_ResizeX :: ImGuiChildFlags Source #
Allow resize from right border (layout direction). Enable .ini saving (unless ImGuiWindowFlags_NoSavedSettings passed to window flags)
pattern ImGuiChildFlags_AlwaysUseWindowPadding :: ImGuiChildFlags Source #
Pad with style.WindowPadding even if no border are drawn (no padding by default for non-bordered child windows because it makes more sense)
pattern ImGuiChildFlags_Border :: ImGuiChildFlags Source #
Show an outer border and enable WindowPadding. (IMPORTANT: this is always == 1 == true for legacy reason)
pattern ImGuiChildFlags_None :: ImGuiChildFlags Source #
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_NoInputs :: ImGuiWindowFlags Source #
- Internal
pattern ImGuiWindowFlags_NoDecoration :: ImGuiWindowFlags Source #
pattern ImGuiWindowFlags_NoNav :: ImGuiWindowFlags Source #
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_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_MenuBar :: ImGuiWindowFlags Source #
Has a menu-bar
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
pattern ImGuiWindowFlags_NoTitleBar :: ImGuiWindowFlags Source #
Disable title-bar
pattern ImGuiWindowFlags_None :: ImGuiWindowFlags Source #
Instances
Instances
Instances
data ImGuiContext Source #
DearImGui context handle.
data ImFontConfig Source #
Font configuration handle.
data ImFontGlyphRangesBuilder Source #
Glyph ranges builder handle.
data ImDrawList Source #
Opaque DrawList handle.
data ImGuiListClipper Source #
ListClipper
pointer tag.
data ImGuiPayload Source #
Payload
pointer tag.
A unique ID used by widgets (typically the result of hashing a stack of string) unsigned Integer (same as ImU32)
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!
Instances
Storable ImGuiTableSortSpecs Source # | |
Defined in DearImGui.Structs sizeOf :: ImGuiTableSortSpecs -> Int # alignment :: ImGuiTableSortSpecs -> Int # peekElemOff :: Ptr ImGuiTableSortSpecs -> Int -> IO ImGuiTableSortSpecs # pokeElemOff :: Ptr ImGuiTableSortSpecs -> Int -> ImGuiTableSortSpecs -> IO () # peekByteOff :: Ptr b -> Int -> IO ImGuiTableSortSpecs # pokeByteOff :: Ptr b -> Int -> ImGuiTableSortSpecs -> IO () # peek :: Ptr ImGuiTableSortSpecs -> IO ImGuiTableSortSpecs # poke :: Ptr ImGuiTableSortSpecs -> ImGuiTableSortSpecs -> IO () # | |
Show ImGuiTableSortSpecs Source # | |
Defined in DearImGui.Structs showsPrec :: Int -> ImGuiTableSortSpecs -> ShowS # show :: ImGuiTableSortSpecs -> String # showList :: [ImGuiTableSortSpecs] -> ShowS # | |
Eq ImGuiTableSortSpecs Source # | |
Defined in DearImGui.Structs (==) :: ImGuiTableSortSpecs -> ImGuiTableSortSpecs -> Bool # (/=) :: ImGuiTableSortSpecs -> ImGuiTableSortSpecs -> Bool # |
data ImGuiTableColumnSortSpecs Source #
Sorting specification for one column of a table
ImGuiTableColumnSortSpecs | |
|
Instances
Storable ImGuiTableColumnSortSpecs Source # | |
Defined in DearImGui.Structs sizeOf :: ImGuiTableColumnSortSpecs -> Int # alignment :: ImGuiTableColumnSortSpecs -> Int # peekElemOff :: Ptr ImGuiTableColumnSortSpecs -> Int -> IO ImGuiTableColumnSortSpecs # pokeElemOff :: Ptr ImGuiTableColumnSortSpecs -> Int -> ImGuiTableColumnSortSpecs -> IO () # peekByteOff :: Ptr b -> Int -> IO ImGuiTableColumnSortSpecs # pokeByteOff :: Ptr b -> Int -> ImGuiTableColumnSortSpecs -> IO () # peek :: Ptr ImGuiTableColumnSortSpecs -> IO ImGuiTableColumnSortSpecs # poke :: Ptr ImGuiTableColumnSortSpecs -> ImGuiTableColumnSortSpecs -> IO () # | |
Show ImGuiTableColumnSortSpecs Source # | |
Defined in DearImGui.Structs showsPrec :: Int -> ImGuiTableColumnSortSpecs -> ShowS # show :: ImGuiTableColumnSortSpecs -> String # showList :: [ImGuiTableColumnSortSpecs] -> ShowS # | |
Eq ImGuiTableColumnSortSpecs Source # | |
Defined in DearImGui.Structs |