Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Bindings to raygui
raygui is an immediate-mode GUI library built on top of raylib. The C version of raygui involves a lot of pointers because of the way it is designed. Unfortunately, this is problematic when binding it to Haskell, as Haskell's immutability makes it difficult to represent pointers properly. This means many functions will take the previous state of a control as an argument and return the updated state of that control.
Keep in mind that raygui is an immediate mode GUI, so it is designed mostly for debugging and development and not for actual game GUIs. To this end, it is not very customizable and the features are quite limited. For a real game, you should make your own retained mode GUI.
Synopsis
- guiEnable :: IO ()
- guiDisable :: IO ()
- guiLock :: IO ()
- guiUnlock :: IO ()
- guiIsLocked :: IO Bool
- guiSetAlpha :: Float -> IO ()
- guiSetState :: GuiState -> IO ()
- guiGetState :: IO GuiState
- guiSetFont :: Font -> IO ()
- guiGetFont :: IO Font
- guiSetStyle :: Enum e => GuiControl -> e -> Int -> IO ()
- guiSetStyleC :: Enum e => GuiControl -> e -> Color -> IO ()
- guiSetStyleE :: (Enum e, Enum v) => GuiControl -> e -> v -> IO ()
- guiSetStyleBorderColorNormal :: GuiControl -> Color -> IO ()
- guiSetStyleBaseColorNormal :: GuiControl -> Color -> IO ()
- guiSetStyleTextColorNormal :: GuiControl -> Color -> IO ()
- guiSetStyleBorderColorFocused :: GuiControl -> Color -> IO ()
- guiSetStyleBaseColorFocused :: GuiControl -> Color -> IO ()
- guiSetStyleTextColorFocused :: GuiControl -> Color -> IO ()
- guiSetStyleBorderColorPressed :: GuiControl -> Color -> IO ()
- guiSetStyleBaseColorPressed :: GuiControl -> Color -> IO ()
- guiSetStyleTextColorPressed :: GuiControl -> Color -> IO ()
- guiSetStyleBorderColorDisabled :: GuiControl -> Color -> IO ()
- guiSetStyleBaseColorDisabled :: GuiControl -> Color -> IO ()
- guiSetStyleTextColorDisabled :: GuiControl -> Color -> IO ()
- guiSetStyleBorderWidth :: GuiControl -> Int -> IO ()
- guiSetStyleTextPadding :: GuiControl -> Int -> IO ()
- guiSetStyleTextAlignment :: GuiControl -> GuiTextAlignment -> IO ()
- guiSetStyleTextSize :: Int -> IO ()
- guiSetStyleTextSpacing :: Int -> IO ()
- guiSetStyleLineColor :: Color -> IO ()
- guiSetStyleBackgroundColor :: Color -> IO ()
- guiSetStyleTextLineSpacing :: Int -> IO ()
- guiSetStyleTextAlignmentVertical :: GuiTextAlignmentVertical -> IO ()
- guiSetStyleTextWrapMode :: GuiTextWrapMode -> IO ()
- guiGetStyle :: Enum e => GuiControl -> e -> IO Int
- guiGetStyleC :: Enum e => GuiControl -> e -> IO Color
- guiGetStyleE :: (Enum e, Enum v) => GuiControl -> e -> IO v
- guiGetStyleBorderColorNormal :: GuiControl -> IO Color
- guiGetStyleBaseColorNormal :: GuiControl -> IO Color
- guiGetStyleTextColorNormal :: GuiControl -> IO Color
- guiGetStyleBorderColorFocused :: GuiControl -> IO Color
- guiGetStyleBaseColorFocused :: GuiControl -> IO Color
- guiGetStyleTextColorFocused :: GuiControl -> IO Color
- guiGetStyleBorderColorPressed :: GuiControl -> IO Color
- guiGetStyleBaseColorPressed :: GuiControl -> IO Color
- guiGetStyleTextColorPressed :: GuiControl -> IO Color
- guiGetStyleBorderColorDisabled :: GuiControl -> IO Color
- guiGetStyleBaseColorDisabled :: GuiControl -> IO Color
- guiGetStyleTextColorDisabled :: GuiControl -> IO Color
- guiGetStyleBorderWidth :: GuiControl -> IO Int
- guiGetStyleTextPadding :: GuiControl -> IO Int
- guiGetStyleTextAlignment :: GuiControl -> IO GuiTextAlignment
- guiGetStyleTextSize :: IO Int
- guiGetStyleTextSpacing :: IO Int
- guiGetStyleLineColor :: IO Color
- guiGetStyleBackgroundColor :: IO Color
- guiGetStyleTextLineSpacing :: IO Int
- guiGetStyleTextAlignmentVertical :: IO GuiTextAlignmentVertical
- guiGetStyleTextWrapMode :: IO GuiTextWrapMode
- guiLoadStyle :: String -> IO ()
- guiLoadStyleDefault :: IO ()
- guiEnableTooltip :: IO ()
- guiDisableTooltip :: IO ()
- guiSetTooltip :: String -> IO ()
- guiIconText :: GuiIconName -> String -> IO String
- guiSetIconScale :: Int -> IO ()
- guiGetIcons :: IO (Ptr CUInt)
- guiLoadIcons :: String -> Bool -> Int -> IO [String]
- guiDrawIcon :: GuiIconName -> Int -> Int -> Int -> Color -> IO ()
- guiWindowBox :: Rectangle -> Maybe String -> IO Bool
- guiGroupBox :: Rectangle -> Maybe String -> IO ()
- guiLine :: Rectangle -> Maybe String -> IO ()
- guiPanel :: Rectangle -> Maybe String -> IO ()
- guiTabBar :: Rectangle -> [String] -> Maybe Int -> IO (Int, Maybe Int)
- guiScrollPanel :: Rectangle -> Maybe String -> Rectangle -> Maybe Vector2 -> Maybe Rectangle -> IO (Vector2, Rectangle)
- guiLabel :: Rectangle -> String -> IO ()
- guiButton :: Rectangle -> Maybe String -> IO Bool
- guiLabelButton :: Rectangle -> Maybe String -> IO Bool
- guiToggle :: Rectangle -> Maybe String -> Bool -> IO Bool
- guiToggleGroup :: Rectangle -> String -> Maybe Int -> IO Int
- guiToggleSlider :: Rectangle -> String -> Maybe Int -> IO (Bool, Int)
- guiCheckBox :: Rectangle -> Maybe String -> Bool -> IO Bool
- guiComboBox :: Rectangle -> String -> Maybe Int -> IO Int
- guiDropdownBox :: Rectangle -> String -> Maybe Int -> Bool -> IO (Bool, Int)
- guiSpinner :: Rectangle -> Maybe String -> Int -> Int -> Int -> Bool -> IO (Bool, Int)
- guiValueBox :: Rectangle -> Maybe String -> Int -> Int -> Int -> Bool -> IO (Bool, Int)
- guiValueBoxFloat :: Rectangle -> Maybe String -> String -> Maybe Int -> Float -> Bool -> IO (Bool, Float, String)
- guiTextBox :: Rectangle -> String -> Maybe Int -> Bool -> IO (Bool, String)
- guiSlider :: Rectangle -> Maybe String -> Maybe String -> Float -> Float -> Float -> IO (Bool, Float)
- guiSliderBar :: Rectangle -> Maybe String -> Maybe String -> Float -> Float -> Float -> IO (Bool, Float)
- guiProgressBar :: Rectangle -> Maybe String -> Maybe String -> Float -> Float -> Float -> IO Float
- guiStatusBar :: Rectangle -> String -> IO ()
- guiDummyRec :: Rectangle -> String -> IO ()
- guiGrid :: Rectangle -> Float -> Int -> IO (Maybe Vector2)
- guiListView :: Rectangle -> String -> Int -> Maybe Int -> IO (Int, Maybe Int)
- guiListViewEx :: Rectangle -> [String] -> Int -> Maybe Int -> Maybe Int -> IO (Int, Maybe Int, Maybe Int)
- guiMessageBox :: Rectangle -> Maybe String -> String -> String -> IO (Maybe Int)
- guiTextInputBox :: Rectangle -> Maybe String -> String -> String -> String -> Maybe Int -> Maybe Bool -> IO (Maybe Bool, String, Maybe Int)
- guiColorPicker :: Rectangle -> Maybe Color -> IO Color
- guiColorPanel :: Rectangle -> Maybe Color -> IO Color
- guiColorBarAlpha :: Rectangle -> Float -> IO Float
- guiColorBarHue :: Rectangle -> Float -> IO Float
- guiColorPickerHSV :: Rectangle -> Maybe Vector3 -> IO Vector3
- guiColorPanelHSV :: Rectangle -> Maybe Vector3 -> IO Vector3
- c'guiEnable :: IO ()
- c'guiDisable :: IO ()
- c'guiLock :: IO ()
- c'guiUnlock :: IO ()
- c'guiIsLocked :: IO CBool
- c'guiSetAlpha :: CFloat -> IO ()
- c'guiSetState :: CInt -> IO ()
- c'guiGetState :: IO CInt
- c'guiSetFont :: Ptr Font -> IO ()
- c'guiGetFont :: IO (Ptr Font)
- c'guiSetStyle :: CInt -> CInt -> CInt -> IO ()
- c'guiGetStyle :: CInt -> CInt -> IO CInt
- c'guiLoadStyle :: CString -> IO ()
- c'guiLoadStyleDefault :: IO ()
- c'guiEnableTooltip :: IO ()
- c'guiDisableTooltip :: IO ()
- c'guiSetTooltip :: CString -> IO ()
- c'guiIconText :: CInt -> CString -> IO CString
- c'guiSetIconScale :: CInt -> IO ()
- c'guiGetIcons :: IO (Ptr CUInt)
- c'guiLoadIcons :: CString -> CBool -> IO (Ptr CString)
- c'guiDrawIcon :: CInt -> CInt -> CInt -> CInt -> Ptr Color -> IO ()
- c'guiWindowBox :: Ptr Rectangle -> CString -> IO CInt
- c'guiGroupBox :: Ptr Rectangle -> CString -> IO CInt
- c'guiLine :: Ptr Rectangle -> CString -> IO CInt
- c'guiPanel :: Ptr Rectangle -> CString -> IO CInt
- c'guiTabBar :: Ptr Rectangle -> Ptr CString -> CInt -> Ptr CInt -> IO CInt
- c'guiScrollPanel :: Ptr Rectangle -> CString -> Ptr Rectangle -> Ptr Vector2 -> Ptr Rectangle -> IO CInt
- c'guiLabel :: Ptr Rectangle -> CString -> IO CInt
- c'guiButton :: Ptr Rectangle -> CString -> IO CInt
- c'guiLabelButton :: Ptr Rectangle -> CString -> IO CInt
- c'guiToggle :: Ptr Rectangle -> CString -> Ptr CBool -> IO CInt
- c'guiToggleGroup :: Ptr Rectangle -> CString -> Ptr CInt -> IO CInt
- c'guiToggleSlider :: Ptr Rectangle -> CString -> Ptr CInt -> IO CInt
- c'guiCheckBox :: Ptr Rectangle -> CString -> Ptr CBool -> IO CInt
- c'guiComboBox :: Ptr Rectangle -> CString -> Ptr CInt -> IO CInt
- c'guiDropdownBox :: Ptr Rectangle -> CString -> Ptr CInt -> CBool -> IO CInt
- c'guiSpinner :: Ptr Rectangle -> CString -> Ptr CInt -> CInt -> CInt -> CBool -> IO CInt
- c'guiValueBox :: Ptr Rectangle -> CString -> Ptr CInt -> CInt -> CInt -> CBool -> IO CInt
- c'guiValueBoxFloat :: Ptr Rectangle -> CString -> CString -> Ptr CFloat -> CBool -> IO CInt
- c'guiTextBox :: Ptr Rectangle -> CString -> CInt -> CBool -> IO CInt
- c'guiSlider :: Ptr Rectangle -> CString -> CString -> Ptr CFloat -> CFloat -> CFloat -> IO CInt
- c'guiSliderBar :: Ptr Rectangle -> CString -> CString -> Ptr CFloat -> CFloat -> CFloat -> IO CInt
- c'guiProgressBar :: Ptr Rectangle -> CString -> CString -> Ptr CFloat -> CFloat -> CFloat -> IO CInt
- c'guiStatusBar :: Ptr Rectangle -> CString -> IO CInt
- c'guiDummyRec :: Ptr Rectangle -> CString -> IO CInt
- c'guiGrid :: Ptr Rectangle -> CString -> CFloat -> CInt -> Ptr Vector2 -> IO CInt
- c'guiListView :: Ptr Rectangle -> CString -> Ptr CInt -> Ptr CInt -> IO CInt
- c'guiListViewEx :: Ptr Rectangle -> Ptr CString -> CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> IO CInt
- c'guiMessageBox :: Ptr Rectangle -> CString -> CString -> CString -> IO CInt
- c'guiTextInputBox :: Ptr Rectangle -> CString -> CString -> CString -> CString -> CInt -> Ptr CBool -> IO CInt
- c'guiColorPicker :: Ptr Rectangle -> CString -> Ptr Color -> IO CInt
- c'guiColorPanel :: Ptr Rectangle -> CString -> Ptr Color -> IO CInt
- c'guiColorBarAlpha :: Ptr Rectangle -> CString -> Ptr CFloat -> IO CInt
- c'guiColorBarHue :: Ptr Rectangle -> CString -> Ptr CFloat -> IO CInt
- c'guiColorPickerHSV :: Ptr Rectangle -> CString -> Ptr Vector3 -> IO CInt
- c'guiColorPanelHSV :: Ptr Rectangle -> CString -> Ptr Vector3 -> IO CInt
High level
Global gui state control functions
guiDisable :: IO () Source #
Disable gui controls (global state)
guiIsLocked :: IO Bool Source #
Check if gui is locked (global state)
guiSetAlpha :: Float -> IO () Source #
Set gui controls alpha (global state), alpha goes from 0.0f to 1.0f
guiSetState :: GuiState -> IO () Source #
Set gui state (global state)
guiGetState :: IO GuiState Source #
Get gui state (global state)
Font set/get functions
guiSetFont :: Font -> IO () Source #
Set gui custom font (global state)
guiGetFont :: IO Font Source #
Get gui custom font (global state)
Style set/get functions
In the native C code, there is just one guiSetStyle
function and one
guiGetStyle
function, which take a property type and an int
as the
property value. This int
can represent a plain integer, a Color
,
or an enum, depending on the property type. This is very un-Haskelly
behavior and not very user friendly (as it requires the use of
colorToInt
and such), so they have been split into 3 setters and
getters, one for regular Int
s, one for Color
s, and one for
Enum
s. There are also a bunch of specialized getters and setters for
commonly used properties.
Set style
guiSetStyle :: Enum e => GuiControl -> e -> Int -> IO () Source #
Set style property as Int
guiSetStyleC :: Enum e => GuiControl -> e -> Color -> IO () Source #
Set style property as Color
guiSetStyleE :: (Enum e, Enum v) => GuiControl -> e -> v -> IO () Source #
Set style property as Enum
guiSetStyleBorderColorNormal :: GuiControl -> Color -> IO () Source #
Set BORDER_COLOR_NORMAL style property | Control border color in STATE_NORMAL
guiSetStyleBaseColorNormal :: GuiControl -> Color -> IO () Source #
Set BASE_COLOR_NORMAL style property | Control base color in STATE_NORMAL
guiSetStyleTextColorNormal :: GuiControl -> Color -> IO () Source #
Set TEXT_COLOR_NORMAL style property | Control text color in STATE_NORMAL
guiSetStyleBorderColorFocused :: GuiControl -> Color -> IO () Source #
Set BORDER_COLOR_FOCUSED style property | Control border color in STATE_FOCUSED
guiSetStyleBaseColorFocused :: GuiControl -> Color -> IO () Source #
Set BASE_COLOR_FOCUSED style property | Control base color in STATE_FOCUSED
guiSetStyleTextColorFocused :: GuiControl -> Color -> IO () Source #
Set TEXT_COLOR_FOCUSED style property | Control text color in STATE_FOCUSED
guiSetStyleBorderColorPressed :: GuiControl -> Color -> IO () Source #
Set BORDER_COLOR_PRESSED style property | Control border color in STATE_PRESSED
guiSetStyleBaseColorPressed :: GuiControl -> Color -> IO () Source #
Set BASE_COLOR_PRESSED style property | Control base color in STATE_PRESSED
guiSetStyleTextColorPressed :: GuiControl -> Color -> IO () Source #
Set TEXT_COLOR_PRESSED style property | Control text color in STATE_PRESSED
guiSetStyleBorderColorDisabled :: GuiControl -> Color -> IO () Source #
Set BORDER_COLOR_DISABLED style property | Control border color in STATE_DISABLED
guiSetStyleBaseColorDisabled :: GuiControl -> Color -> IO () Source #
Set BASE_COLOR_DISABLED style property | Control base color in STATE_DISABLED
guiSetStyleTextColorDisabled :: GuiControl -> Color -> IO () Source #
Set TEXT_COLOR_DISABLED style property | Control text color in STATE_DISABLED
guiSetStyleBorderWidth :: GuiControl -> Int -> IO () Source #
Set BORDER_WIDTH style property | Control border size, 0 for no border
guiSetStyleTextPadding :: GuiControl -> Int -> IO () Source #
Set TEXT_PADDING style property | Control text padding, not considering border
guiSetStyleTextAlignment :: GuiControl -> GuiTextAlignment -> IO () Source #
Set TEXT_ALIGNMENT style property | Control text horizontal alignment inside control text bound (after border and padding)
guiSetStyleTextSize :: Int -> IO () Source #
Set TEXT_SIZE default style property | Text size (glyphs max height)
guiSetStyleTextSpacing :: Int -> IO () Source #
Set TEXT_SPACING default style property | Text spacing between glyphs
guiSetStyleLineColor :: Color -> IO () Source #
Set LINE_COLOR default style property | Line control color
guiSetStyleBackgroundColor :: Color -> IO () Source #
Set BACKGROUND_COLOR default style property | Background color
guiSetStyleTextLineSpacing :: Int -> IO () Source #
Set TEXT_LINE_SPACING default style property | Text spacing between lines
guiSetStyleTextAlignmentVertical :: GuiTextAlignmentVertical -> IO () Source #
Set TEXT_ALIGNMENT_VERTICAL default style property | Text vertical alignment inside text bounds (after border and padding)
guiSetStyleTextWrapMode :: GuiTextWrapMode -> IO () Source #
Set TEXT_WRAP_MODE default style property | Text wrap-mode inside text bounds
Get style
guiGetStyle :: Enum e => GuiControl -> e -> IO Int Source #
Get style property as Int
guiGetStyleC :: Enum e => GuiControl -> e -> IO Color Source #
Set style property as Color
guiGetStyleE :: (Enum e, Enum v) => GuiControl -> e -> IO v Source #
Set style property as Enum
guiGetStyleBorderColorNormal :: GuiControl -> IO Color Source #
Get BORDER_COLOR_NORMAL style property | Control border color in STATE_NORMAL
guiGetStyleBaseColorNormal :: GuiControl -> IO Color Source #
Get BASE_COLOR_NORMAL style property | Control base color in STATE_NORMAL
guiGetStyleTextColorNormal :: GuiControl -> IO Color Source #
Get TEXT_COLOR_NORMAL style property | Control text color in STATE_NORMAL
guiGetStyleBorderColorFocused :: GuiControl -> IO Color Source #
Get BORDER_COLOR_FOCUSED style property | Control border color in STATE_FOCUSED
guiGetStyleBaseColorFocused :: GuiControl -> IO Color Source #
Get BASE_COLOR_FOCUSED style property | Control base color in STATE_FOCUSED
guiGetStyleTextColorFocused :: GuiControl -> IO Color Source #
Get TEXT_COLOR_FOCUSED style property | Control text color in STATE_FOCUSED
guiGetStyleBorderColorPressed :: GuiControl -> IO Color Source #
Get BORDER_COLOR_PRESSED style property | Control border color in STATE_PRESSED
guiGetStyleBaseColorPressed :: GuiControl -> IO Color Source #
Get BASE_COLOR_PRESSED style property | Control base color in STATE_PRESSED
guiGetStyleTextColorPressed :: GuiControl -> IO Color Source #
Get TEXT_COLOR_PRESSED style property | Control text color in STATE_PRESSED
guiGetStyleBorderColorDisabled :: GuiControl -> IO Color Source #
Get BORDER_COLOR_DISABLED style property | Control border color in STATE_DISABLED
guiGetStyleBaseColorDisabled :: GuiControl -> IO Color Source #
Get BASE_COLOR_DISABLED style property | Control base color in STATE_DISABLED
guiGetStyleTextColorDisabled :: GuiControl -> IO Color Source #
Get TEXT_COLOR_DISABLED style property | Control text color in STATE_DISABLED
guiGetStyleBorderWidth :: GuiControl -> IO Int Source #
Get BORDER_WIDTH style property | Control border size, 0 for no border
guiGetStyleTextPadding :: GuiControl -> IO Int Source #
Get TEXT_PADDING style property | Control text padding, not considering border
guiGetStyleTextAlignment :: GuiControl -> IO GuiTextAlignment Source #
Get TEXT_ALIGNMENT style property | Control text horizontal alignment inside control text bound (after border and padding)
guiGetStyleTextSize :: IO Int Source #
Get TEXT_SIZE default style property | Text size (glyphs max height)
guiGetStyleTextSpacing :: IO Int Source #
Get TEXT_SPACING default style property | Text spacing between glyphs
guiGetStyleLineColor :: IO Color Source #
Get LINE_COLOR default style property | Line control color
guiGetStyleBackgroundColor :: IO Color Source #
Get BACKGROUND_COLOR default style property | Background color
guiGetStyleTextLineSpacing :: IO Int Source #
Get TEXT_LINE_SPACING default style property | Text spacing between lines
guiGetStyleTextAlignmentVertical :: IO GuiTextAlignmentVertical Source #
Get TEXT_ALIGNMENT_VERTICAL default style property | Text vertical alignment inside text bounds (after border and padding)
guiGetStyleTextWrapMode :: IO GuiTextWrapMode Source #
Get TEXT_WRAP_MODE default style property | Text wrap-mode inside text bounds
Styles loading functions
guiLoadStyle :: String -> IO () Source #
Load style file over global style variable (.rgs)
guiLoadStyleDefault :: IO () Source #
Load style default over global style
Tooltips management functions
guiEnableTooltip :: IO () Source #
Enable gui tooltips (global state)
guiDisableTooltip :: IO () Source #
Disable gui tooltips (global state)
guiSetTooltip :: String -> IO () Source #
Set tooltip string
Icons functionality
guiIconText :: GuiIconName -> String -> IO String Source #
Get text with icon id prepended (if supported)
guiSetIconScale :: Int -> IO () Source #
Set default icon drawing size
Load raygui icons file (.rgi) into internal icons data
guiDrawIcon :: GuiIconName -> Int -> Int -> Int -> Color -> IO () Source #
Draw icon using pixel size at specified position
Controls
Container/separator controls, useful for controls organization
Window Box control, shows a window that can be closed
:: Rectangle | |
-> [String] | |
-> Maybe Int | The currently active tab's index, use |
-> IO (Int, Maybe Int) | A tuple, the first element is the index of the active tab, the second element is the tab whose close button is pressed (if any) |
Tab Bar control
:: Rectangle | |
-> Maybe String | |
-> Rectangle | |
-> Maybe Vector2 | The panel's scroll vector, use |
-> Maybe Rectangle | The panel's view rectangle, use |
-> IO (Vector2, Rectangle) | The panel's updated scroll vector and view rectangle as a tuple |
Scroll Panel control
Basic controls set
guiLabelButton :: Rectangle -> Maybe String -> IO Bool Source #
Label button control, returns true when clicked
:: Rectangle | |
-> String | The names of the toggles, separated with semicolons |
-> Maybe Int | The currently active toggle's index, use |
-> IO Int | The updated active toggle index |
Toggle Group control
:: Rectangle | |
-> String | The names of the toggles, separated with semicolons |
-> Maybe Int | The currently active toggle's index, use |
-> IO (Bool, Int) | A tuple, the first element is whether the slider was clicked, the second element is the updated toggle index |
Toggle Slider control
:: Rectangle | |
-> Maybe String | |
-> Bool | The current checkbox state (checked/unchecked) |
-> IO Bool | The updated checkbox state (checked/unchecked) |
Check Box control
:: Rectangle | |
-> String | The names of the combobox options, separated with semicolons |
-> Maybe Int | The currently active option's index, use |
-> IO Int | The updated active option index |
Combo Box control
:: Rectangle | |
-> String | The names of the dropdown options, separated with semicolons |
-> Maybe Int | The currently active option's index, use |
-> Bool |
|
-> IO (Bool, Int) | A tuple, the first element is whether the dropdown was clicked (i.e. the open/closed mode should be toggled), the second element is the updated toggle index |
Dropdown Box control
:: Rectangle | |
-> Maybe String | |
-> Int | The current value |
-> Int | |
-> Int | |
-> Bool | |
-> IO (Bool, Int) | A tuple, the first element is whether the spinner was toggled (i.e. the edit mode should be toggled), the second element is the updated value |
Spinner control
:: Rectangle | |
-> Maybe String | |
-> Int | The current value |
-> Int | |
-> Int | |
-> Bool | |
-> IO (Bool, Int) | A tuple, the first element is whether the value box was toggled (i.e. the edit mode should be toggled), the second element is the updated value |
Value Box control, updates input text with numbers
:: Rectangle | |
-> Maybe String | |
-> String | The current text representation |
-> Maybe Int | Text representation buffer size; if |
-> Float | The current value |
-> Bool | |
-> IO (Bool, Float, String) | A tuple, the first element is whether the value box was toggled (i.e. the edit mode should be toggled), the second and thirds elements are the updated value and text representation |
Value box control for float values
:: Rectangle | |
-> String | |
-> Maybe Int | Text box buffer size; if |
-> Bool | |
-> IO (Bool, String) | A tuple, the first element is whether the text box was toggled (i.e. the edit mode should be toggled), the second element is the updated text box value |
Text Box control, updates input text
:: Rectangle | |
-> Maybe String | |
-> Maybe String | |
-> Float | The current value |
-> Float | |
-> Float | |
-> IO (Bool, Float) | A tuple, the first element is whether the slider was edited, the second element is the updated value |
Slider control
:: Rectangle | |
-> Maybe String | |
-> Maybe String | |
-> Float | The current value |
-> Float | |
-> Float | |
-> IO (Bool, Float) | A tuple, the first element is whether the slider bar was edited, the second element is the updated value |
Slider Bar control
:: Rectangle | |
-> Maybe String | |
-> Maybe String | |
-> Float | The current value |
-> Float | |
-> Float | |
-> IO Float | The updated value (clamped to min/max range) |
Progress Bar control
Grid control
Advanced controls set
:: Rectangle | |
-> String | The names of the list options, separated with semicolons |
-> Int | Current scroll index |
-> Maybe Int | Currently selected option index (active index) |
-> IO (Int, Maybe Int) | A tuple, the first element is the updated scroll index, the second element is the updated active index |
List View control
:: Rectangle | |
-> [String] | The names of the list options |
-> Int | Current scroll index |
-> Maybe Int | Currently selected option index (active index) |
-> Maybe Int | Currently focused option index |
-> IO (Int, Maybe Int, Maybe Int) | A tuple, the first element is the updated scroll index, the second element is the updated active index, the third element is the updated focus index |
List View with extended parameters
:: Rectangle | |
-> Maybe String | |
-> String | |
-> String | Button labels separated by semicolons |
-> IO (Maybe Int) | The index of the clicked button, if any (0 = close message box, 1,2,... = custom button) |
Message Box control, displays a message
:: Rectangle | |
-> Maybe String | |
-> String | |
-> String | Button names, separated by semicolons |
-> String | Current text box value |
-> Maybe Int | Text box buffer size; if |
-> Maybe Bool | Secret (password) mode; `Just True` if the value should be censored;
`Just False` if it should not be censored but there should still be a
button to hide it; |
-> IO (Maybe Bool, String, Maybe Int) | A tuple, the first element is the updated secret mode, the second element is the updated text box value, the third element is the index of the clicked button, if any (0 = close input box, 1,2,... = custom button) |
Text Input Box control, ask for text, supports secret
:: Rectangle | |
-> Maybe Color | Currently selected color, use |
-> IO Color | Updated color |
Color Picker control (multiple color controls)
:: Rectangle | |
-> Maybe Color | Currently selected color, use |
-> IO Color | Updated color |
Color Panel control
Color Bar Alpha control
Color Bar Hue control
:: Rectangle | |
-> Maybe Vector3 | Currently selected color, use |
-> IO Vector3 | Updated color |
Color Picker control that avoids conversion to RGB on each call (multiple color controls)
:: Rectangle | |
-> Maybe Vector3 | Currently selected color, use |
-> IO Vector3 | Updated color |
Color Panel control that updates Hue-Saturation-Value color value, used by guiColorPickerHSV
Native
c'guiEnable :: IO () Source #
c'guiDisable :: IO () Source #
c'guiUnlock :: IO () Source #
c'guiIsLocked :: IO CBool Source #
c'guiSetAlpha :: CFloat -> IO () Source #
c'guiSetState :: CInt -> IO () Source #
c'guiGetState :: IO CInt Source #
c'guiLoadStyle :: CString -> IO () Source #
c'guiLoadStyleDefault :: IO () Source #
c'guiEnableTooltip :: IO () Source #
c'guiDisableTooltip :: IO () Source #
c'guiSetTooltip :: CString -> IO () Source #
c'guiSetIconScale :: CInt -> IO () Source #
c'guiScrollPanel :: Ptr Rectangle -> CString -> Ptr Rectangle -> Ptr Vector2 -> Ptr Rectangle -> IO CInt Source #
c'guiValueBoxFloat :: Ptr Rectangle -> CString -> CString -> Ptr CFloat -> CBool -> IO CInt Source #
c'guiSlider :: Ptr Rectangle -> CString -> CString -> Ptr CFloat -> CFloat -> CFloat -> IO CInt Source #
c'guiSliderBar :: Ptr Rectangle -> CString -> CString -> Ptr CFloat -> CFloat -> CFloat -> IO CInt Source #
c'guiProgressBar :: Ptr Rectangle -> CString -> CString -> Ptr CFloat -> CFloat -> CFloat -> IO CInt Source #
c'guiListViewEx :: Ptr Rectangle -> Ptr CString -> CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> IO CInt Source #