fltkhs-themes-0.2.0.0: A set of themed widgets that provides drop in replacements to the ones in FLTKHS.

Safe HaskellNone
LanguageHaskell2010

Graphics.UI.FLTK.Theme.Light

Contents

Description

A Light theme for FLTKHS.

Synopsis

Motivation

This package tries to make it easy to write nice consistent-looking FLTKHS applications by providing drop-in light themed replacement widgets to the standard ones with minimal performance and memory overhead. While FLTK itself has very good performance and memory usage the default look of the widgets is quite dated; this package aims to bridge that gap by providing a more modern interface while retaining the responsiveness.

NOTE: This is not a theme in the same sense as CSS; the look is achieved simply providing a custom drawing routine for each widget.

Inspiration

The Light theme is massively indebted to and steals shamelessly from the excellent Qooxdoo project which manages to create a very slick interface which is at the same time production-grade and easy to understand and use.

Installation

Installation follows the same basic procedure as FLTKHS. The only difference is that those instructions use the default hello world skeleton whereas for themed UIs you'll want the themed skeleton, so wherever the original instructions tell you to use the default skeleton use the latter instead. And to run it, instead of:

> stack exec fltkhs-hello-world

do

> stack exec fltkhs-light-theme-skeleton

Getting Started

The underlying widget API has not been touched so all of the existing FLTK and FLTKHS documentation still applies which makes switching over from an existing codebase, not entirely but mostly, frictionless.

The simplest app skeleton to get started with this theme is as follows:

{-# LANGUAGE ImplicitParams #-}      -- (1)
module Main where
...
import Graphics.UI.FLTK.Theme.Light  -- (2)
...
main :: IO ()
main = do
  assets <- configureTheme           -- (3)
  let ?assets = assets               -- (3)
  ui
  FL.run
  FL.flush

ui :: (?assets :: Assets) => IO ()   -- (4)
ui = ...

It involves only (1) enabling the ImplicitParams extension, (2) importing this module (3) doing some minor setup before the actual app code and (4) threading the implicit constraint to whatever function uses this theme. Graphics.UI.FLTK.Theme.Light.Assets has more information.

The ImplicitParams requirement is so that widgets have access to the resources needed by this theme (icons, images, fonts etc.). See Graphics.UI.FLTK.Theme.Light.Assets for more information.

Running In the REPL

Assuming you're using the skeleton project getting a GUI running in GHCi is pretty much the same FLTKHS except the command to run the REPL is:

stack ghci --flag fltkhs:bundled fltkhs-light-theme-skeleton:exe:fltkhs-light-theme-skeleton

Deployment

This package bundles a lot of local assets, images and especially fonts so deploying a themed application is not as simple as just adding an executable file to your path. To help with this the skeleton project uses the asset-bundle package to create a ZIP archive of all the assets the application needs at runtime. The package docs have a lot more info but in a nutshell when you build the skeletop app a ZIP archive, fltkhs-light-theme-skeleton_bundled.zip, is generated for you and placed deep inside your .stack-work (or dist-new if you're using Cabal) directory. It contains all the assets and a runner script (run.sh on Linux and OSX and run.bat on Windows) which invokes the executable, passes along all command line arguments and sets up the environment so it can find the assets at runtime.

Demo

In addition to the skeleton project there is a also a small but steadily growing showcase app that gives a better idea of the look-and-feel of this theme. More will be added as time permits.

What's Missing

While most of the widgets and functionality in FLTKHS have and themed analogs but some do not mostly because, in my view, they don't fit into app development much nowadays and so weren't worth porting. If there's a pressing need let me know.

  • Fill and Nice Sliders - here they fallback to the slider provided by the theme.
  • FLTK's Pre-Made Modal Dialogs
  • FLTK's Square Clock
  • Fluid integration - FLTK ships with FLUID GUI builder and the default FLTKHS integrates with it quite well but currently there is no support for using it to create themed apps. This is definitely on the roadmap and should be resolved in the near future.

Assets

The resources bundled with the theme, see the module documentation for more information.

Banners

Some banners

Themed Widgets

Haddock barf

There is no reason to read anything below, this module hides the default widgets it overrides and then re-exports what it doesn't. The re-exported module from FLTKHS in turn re-exports modules from that package. Instead of just showing the exported module as a link Haddock insists on flattening and barfing out all of its contents here. Sorry, didn't know how to get around it.

doubleWindowCustom #

Arguments

:: Size

Size of this window

-> Maybe Position

Optional position of this window

-> Maybe Text

Optional label

-> Maybe (Ref DoubleWindow -> IO ())

Optional table drawing routine

-> CustomWidgetFuncs DoubleWindow

Custom widget overrides

-> CustomWindowFuncs DoubleWindow

Custom window overrides

-> IO (Ref DoubleWindow) 

flAlert :: Text -> IO () #

flMessage :: Text -> IO () #

adjusterCustom #

Arguments

:: Rectangle

The bounds of this Adjuster

-> Maybe Text

The Adjuster label

-> Maybe (Ref Adjuster -> IO ())

Optional custom drawing function

-> Maybe (CustomWidgetFuncs Adjuster)

Optional custom widget functions

-> IO (Ref Adjuster) 

buttonCustom #

Arguments

:: Rectangle

The bounds of this button

-> Maybe Text

The button label

-> Maybe (Ref Button -> IO ())

Optional custom drawing function

-> Maybe (CustomWidgetFuncs Button)

Optional custom widget functions

-> IO (Ref Button) 

checkButtonCustom #

Arguments

:: Rectangle

The bounds of this CheckButton

-> Maybe Text

The CheckButton label

-> Maybe (Ref CheckButton -> IO ())

Optional custom drawing function

-> Maybe (CustomWidgetFuncs CheckButton)

Optional custom widget functions

-> IO (Ref CheckButton) 

choiceCustom #

Arguments

:: Rectangle

The bounds of this Choice

-> Maybe Text

The Choice label

-> Maybe (Ref Choice -> IO ())

Optional custom drawing function

-> Maybe (CustomWidgetFuncs Choice)

Optional custom widget functions

-> IO (Ref Choice) 

clockCustom #

Arguments

:: Rectangle

The bounds of this Clock

-> Maybe Text

The Clock label

-> Maybe (Ref Clock -> IO ())

Optional custom drawing function

-> Maybe (CustomWidgetFuncs Clock)

Optional custom widget functions

-> IO (Ref Clock) 

newtype Hour #

Constructors

Hour Int 
Instances
Show Hour 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Base.Clock

Methods

showsPrec :: Int -> Hour -> ShowS #

show :: Hour -> String #

showList :: [Hour] -> ShowS #

newtype Minute #

Constructors

Minute Int 
Instances
Show Minute 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Base.Clock

newtype Second #

Constructors

Second Int 
Instances
Show Second 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Base.Clock

colorChooserCustom #

Arguments

:: Rectangle

The bounds of this ColorChooser

-> Maybe Text

The ColorChooser label

-> Maybe (Ref ColorChooser -> IO ())

Optional custom drawing function

-> Maybe (CustomColorChooserFuncs ColorChooser) 
-> Maybe (CustomWidgetFuncs ColorChooser)

Optional custom widget functions

-> IO (Ref ColorChooser) 

counterCustom #

Arguments

:: Rectangle

The bounds of this Counter

-> Maybe Text

The Counter label

-> Maybe (Ref Counter -> IO ())

Optional custom drawing function

-> Maybe (CustomWidgetFuncs Counter)

Optional custom widget functions

-> IO (Ref Counter) 

dialCustom #

Arguments

:: Rectangle

The bounds of this Dial

-> Maybe Text

The Dial label

-> Maybe (Ref Dial -> IO ())

Optional custom drawing function

-> Maybe (CustomWidgetFuncs Dial)

Optional custom widget functions

-> IO (Ref Dial) 

fileBrowserCustom #

Arguments

:: Rectangle

The bounds of this FileBrowser

-> Maybe Text

The FileBrowser label

-> Maybe (Ref FileBrowser -> IO ())

Optional custom drawing function

-> Maybe (CustomWidgetFuncs FileBrowser)

Optional custom widget functions

-> IO (Ref FileBrowser) 

type FileSortF = FunPtr (Ptr (Ptr ()) -> Ptr (Ptr ()) -> IO CInt) #

fileInputCustom #

Arguments

:: Rectangle

The bounds of this FileInput

-> Maybe Text

The FileInput label

-> Maybe (Ref FileInput -> IO ())

Optional custom drawing function

-> Maybe (CustomWidgetFuncs FileInput)

Optional custom widget functions

-> IO (Ref FileInput) 

inputCustom #

Arguments

:: Rectangle

The bounds of this Input

-> Maybe Text

The Input label

-> Maybe FlInputType

The input type

-> Maybe (Ref Input -> IO ())

Optional custom drawing function

-> Maybe (CustomWidgetFuncs Input)

Optional custom widget functions

-> IO (Ref Input) 

lightButtonCustom #

Arguments

:: Rectangle

The bounds of this LightButton

-> Maybe Text

The LightButton label

-> Maybe (Ref LightButton -> IO ())

Optional custom drawing function

-> Maybe (CustomWidgetFuncs LightButton)

Optional custom widget functions

-> IO (Ref LightButton) 

menuBarCustom #

Arguments

:: Rectangle

The bounds of this MenuBar

-> Maybe Text

The MenuBar label

-> Maybe (Ref MenuBar -> IO ())

Optional custom drawing function

-> Maybe (CustomWidgetFuncs MenuBar)

Optional custom widget functions

-> IO (Ref MenuBar) 

menuButtonCustom #

Arguments

:: Rectangle

The bounds of this MenuButton

-> Maybe Text

The MenuButton label

-> Maybe (Ref MenuButton -> IO ())

Optional custom drawing function

-> Maybe (CustomWidgetFuncs MenuButton)

Optional custom widget functions

-> IO (Ref MenuButton) 

sysMenuBarCustom #

Arguments

:: Rectangle

The bounds of this SysMenuBar

-> Maybe Text

The SysMenuBar label

-> Maybe (Ref SysMenuBar -> IO ())

Optional custom drawing function

-> Maybe (CustomWidgetFuncs SysMenuBar)

Optional custom widget functions

-> IO (Ref SysMenuBar) 

newtype MenuItemName #

Constructors

MenuItemName Text 

outputCustom #

Arguments

:: Rectangle

The bounds of this Output

-> Maybe Text

The Output label

-> Maybe (Ref Output -> IO ())

Optional custom drawing function

-> Maybe (CustomWidgetFuncs Output)

Optional custom widget functions

-> IO (Ref Output) 

packCustom #

Arguments

:: Rectangle

The bounds of this Pack

-> Maybe Text

The Pack label

-> Maybe (Ref Pack -> IO ())

Optional custom drawing function

-> Maybe (CustomWidgetFuncs Pack)

Optional custom widget functions

-> IO (Ref Pack) 

positionerCustom #

Arguments

:: Rectangle

The bounds of this Positioner

-> Maybe Text

The Positioner label

-> Maybe (Ref Positioner -> IO ())

Optional custom drawing function

-> Maybe (CustomWidgetFuncs Positioner)

Optional custom widget functions

-> IO (Ref Positioner) 

progressCustom #

Arguments

:: Rectangle

The bounds of this Progress

-> Maybe Text

The Progress label

-> Maybe (Ref Progress -> IO ())

Optional custom drawing function

-> Maybe (CustomWidgetFuncs Progress)

Optional custom widget functions

-> IO (Ref Progress) 

repeatButtonCustom #

Arguments

:: Rectangle

The bounds of this RepeatButton

-> Maybe Text

The RepeatButton label

-> Maybe (Ref RepeatButton -> IO ())

Optional custom drawing function

-> Maybe (CustomWidgetFuncs RepeatButton)

Optional custom widget functions

-> IO (Ref RepeatButton) 

returnButtonCustom #

Arguments

:: Rectangle

The bounds of this ReturnButton

-> Maybe Text

The ReturnButton label

-> Maybe (Ref ReturnButton -> IO ())

Optional custom drawing function

-> Maybe (CustomWidgetFuncs ReturnButton)

Optional custom widget functions

-> IO (Ref ReturnButton) 

rollerCustom #

Arguments

:: Rectangle

The bounds of this Roller

-> Maybe Text

The Roller label

-> Maybe (Ref Roller -> IO ())

Optional custom drawing function

-> Maybe (CustomWidgetFuncs Roller)

Optional custom widget functions

-> IO (Ref Roller) 

roundButtonCustom #

Arguments

:: Rectangle

The bounds of this RoundButton

-> Maybe Text

The RoundButton label

-> Maybe (Ref RoundButton -> IO ())

Optional custom drawing function

-> Maybe (CustomWidgetFuncs RoundButton)

Optional custom widget functions

-> IO (Ref RoundButton) 

scrollbarCustom #

Arguments

:: Rectangle

The bounds of this Scrollbar

-> Maybe Text

The Scrollbar label

-> Maybe (Ref Scrollbar -> IO ())

Optional custom drawing function

-> Maybe (CustomWidgetFuncs Scrollbar)

Optional custom widget functions

-> IO (Ref Scrollbar) 

scrolledCustom #

Arguments

:: Rectangle

The bounds of this Scrolled

-> Maybe Text

The Scrolled label

-> Maybe (Ref Scrolled -> IO ())

Optional custom drawing function

-> Maybe (CustomWidgetFuncs Scrolled)

Optional custom widget functions

-> IO (Ref Scrolled) 

simpleTerminalCustom #

Arguments

:: Rectangle

The bounds of this SimpleTerminal

-> Maybe Text

The SimpleTerminal label

-> Maybe (Ref SimpleTerminal -> IO ())

Optional custom drawing function

-> IO (Ref SimpleTerminal) 

singleWindowCustom #

Arguments

:: Size

Size of this window

-> Maybe Position

Optional position of this window

-> Maybe Text

Optional label

-> Maybe (Ref SingleWindow -> IO ())

Optional custom drawing function

-> CustomWidgetFuncs SingleWindow

Custom widget overrides

-> CustomWindowFuncs SingleWindow

Custom window overrides

-> IO (Ref SingleWindow) 

sliderCustom #

Arguments

:: Rectangle

The bounds of this Slider

-> Maybe Text

The Slider label

-> Maybe (Ref Slider -> IO ())

Optional custom drawing function

-> Maybe (CustomWidgetFuncs Slider)

Optional custom widget functions

-> IO (Ref Slider) 

spinnerCustom #

Arguments

:: Rectangle

The bounds of this Spinner

-> Maybe Text

The Spinner label

-> Maybe (Ref Spinner -> IO ())

Optional custom drawing function

-> Maybe (CustomWidgetFuncs Spinner)

Optional custom widget functions

-> IO (Ref Spinner) 

toDrawCellPrim :: (Ref a -> TableContext -> TableCoordinate -> Rectangle -> IO ()) -> IO (FunPtr (Ptr () -> CInt -> CInt -> CInt -> CInt -> CInt -> CInt -> CInt -> IO ())) #

toSetColumnsPrim :: (Ref a -> Columns -> IO ()) -> IO (FunPtr (Ptr () -> CInt -> IO ())) #

toSetRowsPrim :: (Ref a -> Rows -> IO ()) -> IO (FunPtr (Ptr () -> CInt -> IO ())) #

mkDrawCell :: (Ptr () -> CInt -> CInt -> CInt -> CInt -> CInt -> CInt -> CInt -> IO ()) -> IO (FunPtr (Ptr () -> CInt -> CInt -> CInt -> CInt -> CInt -> CInt -> CInt -> IO ())) #

data Row #

Constructors

Row Int 

data Column #

Constructors

Column Int 

data CustomTableFuncs a #

Constructors

CustomTableFuncs 

Fields

tabsCustom #

Arguments

:: Rectangle

The bounds of this Tabs

-> Maybe Text

The Tabs label

-> Maybe (CustomTabFuncs Tabs)

Optional custom tab drawing functions

-> Maybe (CustomWidgetFuncs Tabs)

Optional custom widget functions

-> IO (Ref Tabs) 

textDisplayCustom #

Arguments

:: Rectangle

The bounds of this TextDisplay

-> Maybe Text

The TextDisplay label

-> Maybe (Ref TextDisplay -> IO ())

Optional custom drawing function

-> Maybe (CustomWidgetFuncs TextDisplay)

Optional custom widget functions

-> IO (Ref TextDisplay) 

textEditorCustom #

Arguments

:: Rectangle

The bounds of this TextEditor

-> Maybe Text

The TextEditor label

-> Maybe (Ref TextEditor -> IO ())

Optional custom drawing function

-> Maybe (CustomWidgetFuncs TextEditor)

Optional custom widget functions

-> IO (Ref TextEditor) 

data KeyFunc where #

Constructors

KeyFunc :: KeyFunc 

type KeyFuncPrim = CInt -> Ptr () -> IO () #

tileCustom #

Arguments

:: Rectangle

The bounds of this Tile

-> Maybe Text

The Tile label

-> Maybe (Ref Tile -> IO ())

Optional custom drawing function

-> Maybe (CustomWidgetFuncs Tile)

Optional custom widget functions

-> IO (Ref Tile) 

treeCustom #

Arguments

:: Rectangle

The bounds of this Tree

-> Maybe Text

The Tree label

-> Maybe (Ref Tree -> IO ())

Optional custom drawing function

-> Maybe (CustomWidgetFuncs Tree)

Optional custom widget functions

-> IO (Ref Tree) 

valueInputCustom #

Arguments

:: Rectangle

The bounds of this ValueInput

-> Maybe Text

The ValueInput label

-> Maybe (Ref ValueInput -> IO ())

Optional custom drawing function

-> Maybe (CustomWidgetFuncs ValueInput)

Optional custom widget functions

-> IO (Ref ValueInput) 

valueOutputCustom #

Arguments

:: Rectangle

The bounds of this ValueOutput

-> Maybe Text

The ValueOutput label

-> Maybe (Ref ValueOutput -> IO ())

Optional custom drawing function

-> Maybe (CustomWidgetFuncs ValueOutput)

Optional custom widget functions

-> IO (Ref ValueOutput) 

valueSliderCustom #

Arguments

:: Rectangle

The bounds of this ValueSlider

-> Maybe Text

The ValueSlider label

-> Maybe (Ref ValueSlider -> IO ())

Optional custom drawing function

-> Maybe (CustomWidgetFuncs ValueSlider)

Optional custom widget functions

-> IO (Ref ValueSlider) 

windowCustom #

Arguments

:: Size

Size of this window

-> Maybe Position

Optional position of this window

-> Maybe Text

Optional label

-> Maybe (Ref Window -> IO ())

Optional table drawing routine

-> CustomWidgetFuncs Window

Custom widget overrides

-> CustomWindowFuncs Window

Custom window overrides

-> IO (Ref Window) 

windowMaker :: (Parent a WindowBase, Parent b WidgetBase) => Size -> Maybe Position -> Maybe Text -> Maybe (Ref b -> IO ()) -> CustomWidgetFuncs b -> CustomWindowFuncs a -> (Int -> Int -> Ptr () -> IO (Ptr ())) -> (Int -> Int -> CString -> Ptr () -> IO (Ptr ())) -> (Int -> Int -> Int -> Int -> Ptr () -> IO (Ptr ())) -> (Int -> Int -> Int -> Int -> CString -> Ptr () -> IO (Ptr ())) -> IO (Ref a) #

data CustomWindowFuncs a #

Constructors

CustomWindowFuncs 

Fields

wizardCustom #

Arguments

:: Rectangle

The bounds of this Wizard

-> Maybe Text

The Wizard label

-> Maybe (Ref Wizard -> IO ())

Optional custom drawing function

-> Maybe (CustomWidgetFuncs Wizard)

Optional custom widget functions

-> IO (Ref Wizard) 

boxCustom #

Arguments

:: Rectangle

The bounds of this box

-> Maybe Text

Optional label

-> Maybe (Ref Box -> IO ())

Optional custom box drawing function

-> Maybe (CustomWidgetFuncs Box)

Optional widget overrides

-> IO (Ref Box) 

widgetCustom #

Arguments

:: Rectangle

The bounds of this widget

-> Maybe Text

The widget label

-> (Ref Widget -> IO ())

Custom drawing function

-> CustomWidgetFuncs Widget

Other custom functions

-> IO (Ref Widget) 

widgetMaker #

Arguments

:: Parent a WidgetBase 
=> Rectangle

Position and size

-> Maybe Text

Title

-> Maybe (Ref a -> IO ())

Custom drawing function

-> Maybe (CustomWidgetFuncs a)

Custom functions

-> (Int -> Int -> Int -> Int -> Ptr () -> IO (Ptr ()))

Foreign constructor to call if only custom functions are given

-> (Int -> Int -> Int -> Int -> CString -> Ptr () -> IO (Ptr ()))

Foreign constructor to call if both title and custom functions are given

-> IO (Ref a)

Reference to the widget

Lots of Widget subclasses have the same constructor parameters. This function consolidates them.

Only of interest to Widget contributors.

defaultCustomWidgetFuncs :: Parent a WidgetBase => CustomWidgetFuncs a #

An empty set of functions to pass to widgetCustom.

defaultDestroyCallbacks :: Ref a -> [Maybe (FunPtr (IO ()))] -> IO () #

customWidgetFunctionStruct :: Parent a WidgetBase => Maybe (Ref a -> IO ()) -> CustomWidgetFuncs a -> IO (Ptr ()) #

Given a record of functions, return a pointer to a struct with function pointers back to those functions.

Only of interest to Widget contributors.

fillCustomWidgetFunctionStruct :: Parent a WidgetBase => Ptr () -> Maybe (Ref a -> IO ()) -> CustomWidgetFuncs a -> IO () #

Fill up a struct with pointers to functions on the Haskell side that will get called instead of the default ones.

Fill up the Widget part the function pointer struct.

Only of interest to Widget contributors

data CustomWidgetFuncs a #

Overrideable Widget functions | Do not create this directly. Instead use defaultWidgetCustomFuncs

Constructors

CustomWidgetFuncs 

Fields

flcEndOffscreen :: IO () #

Only available on FLTK version 1.4.0 and above.

flcCreateOffscreen :: Size -> IO FlOffscreen #

Only available on FLTK version 1.4.0 and above.

flcCursor :: Cursor -> IO () #

flcFrame :: Text -> Rectangle -> IO () #

flcRtlDraw :: Text -> Int -> Position -> IO () #

flcDraw :: Text -> Position -> IO () #

flcGap :: IO () #

flcScale :: ByX -> IO () #

flcYxline :: Position -> Y -> IO () #

flcXylineDownByY :: Position -> X -> Y -> IO () #

flcXyline :: Position -> X -> IO () #

type CustomImageDraw = Ref Image -> Position -> Size -> Maybe X -> Maybe Y -> IO () #

data NativeFileChooserType #

Instances
Enum NativeFileChooserType 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.NativeFileChooser

Eq NativeFileChooserType 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.NativeFileChooser

Ord NativeFileChooserType 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.NativeFileChooser

Show NativeFileChooserType 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.NativeFileChooser

data NativeFileChooserOption #

Instances
Enum NativeFileChooserOption 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.NativeFileChooser

Eq NativeFileChooserOption 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.NativeFileChooser

Ord NativeFileChooserOption 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.NativeFileChooser

Show NativeFileChooserOption 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.NativeFileChooser

checkImage :: (Parent orig RGBImage, Match x ~ FindOp orig orig (GetW ()), Op (GetW ()) x orig (IO Int), Match y ~ FindOp orig orig (Destroy ()), Op (Destroy ()) y orig (IO ())) => Ref orig -> IO (Either UnknownError (Ref orig)) #

newtype TreeItemName #

Constructors

TreeItemName Text 

menuItemLabel :: (HasCallStack, Match r ~ FindOp a a (MenuItemLabel ()), Op (MenuItemLabel ()) r a impl) => Ref a -> impl #

widgetLabel :: (HasCallStack, Match r ~ FindOp a a (WidgetLabel ()), Op (WidgetLabel ()) r a impl) => Ref a -> impl #

removeLines :: (HasCallStack, Match r ~ FindOp a a (RemoveLines ()), Op (RemoveLines ()) r a impl) => Ref a -> impl #

getStyleTableSize :: (HasCallStack, Match r ~ FindOp a a (GetStyleTableSize ()), Op (GetStyleTableSize ()) r a impl) => Ref a -> impl #

getStyleTable :: (HasCallStack, Match r ~ FindOp a a (GetStyleTable ()), Op (GetStyleTable ()) r a impl) => Ref a -> impl #

setStyleTable :: (HasCallStack, Match r ~ FindOp a a (SetStyleTable ()), Op (SetStyleTable ()) r a impl) => Ref a -> impl #

getAnsi :: (HasCallStack, Match r ~ FindOp a a (GetAnsi ()), Op (GetAnsi ()) r a impl) => Ref a -> impl #

setAnsi :: (HasCallStack, Match r ~ FindOp a a (SetAnsi ()), Op (SetAnsi ()) r a impl) => Ref a -> impl #

getHistoryLines :: (HasCallStack, Match r ~ FindOp a a (GetHistoryLines ()), Op (GetHistoryLines ()) r a impl) => Ref a -> impl #

setHistoryLines :: (HasCallStack, Match r ~ FindOp a a (SetHistoryLines ()), Op (SetHistoryLines ()) r a impl) => Ref a -> impl #

getStayAtBottom :: (HasCallStack, Match r ~ FindOp a a (GetStayAtBottom ()), Op (GetStayAtBottom ()) r a impl) => Ref a -> impl #

setStayAtBottom :: (HasCallStack, Match r ~ FindOp a a (SetStayAtBottom ()), Op (SetStayAtBottom ()) r a impl) => Ref a -> impl #

getErrorColor :: (HasCallStack, Match r ~ FindOp a a (GetErrorColor ()), Op (GetErrorColor ()) r a impl) => Ref a -> impl #

setErrorColor :: (HasCallStack, Match r ~ FindOp a a (SetErrorColor ()), Op (SetErrorColor ()) r a impl) => Ref a -> impl #

getFiletype :: (HasCallStack, Match r ~ FindOp a a (GetFiletype ()), Op (GetFiletype ()) r a impl) => Ref a -> impl #

setFiletype :: (HasCallStack, Match r ~ FindOp a a (SetFiletype ()), Op (SetFiletype ()) r a impl) => Ref a -> impl #

getIconsize :: (HasCallStack, Match r ~ FindOp a a (GetIconsize ()), Op (GetIconsize ()) r a impl) => Ref a -> impl #

setIconsize :: (HasCallStack, Match r ~ FindOp a a (SetIconsize ()), Op (SetIconsize ()) r a impl) => Ref a -> impl #

getHsv :: (HasCallStack, Match r ~ FindOp a a (GetHsv ()), Op (GetHsv ()) r a impl) => Ref a -> impl #

getRgb :: (HasCallStack, Match r ~ FindOp a a (GetRgb ()), Op (GetRgb ()) r a impl) => Ref a -> impl #

setRgb :: (HasCallStack, Match r ~ FindOp a a (SetRgb ()), Op (SetRgb ()) r a impl) => Ref a -> impl #

setHsv :: (HasCallStack, Match r ~ FindOp a a (SetHsv ()), Op (SetHsv ()) r a impl) => Ref a -> impl #

getB :: (HasCallStack, Match r ~ FindOp a a (GetB ()), Op (GetB ()) r a impl) => Ref a -> impl #

getG :: (HasCallStack, Match r ~ FindOp a a (GetG ()), Op (GetG ()) r a impl) => Ref a -> impl #

getR :: (HasCallStack, Match r ~ FindOp a a (GetR ()), Op (GetR ()) r a impl) => Ref a -> impl #

getSaturation :: (HasCallStack, Match r ~ FindOp a a (GetSaturation ()), Op (GetSaturation ()) r a impl) => Ref a -> impl #

getHue :: (HasCallStack, Match r ~ FindOp a a (GetHue ()), Op (GetHue ()) r a impl) => Ref a -> impl #

setFormat :: (HasCallStack, Match r ~ FindOp a a (SetFormat ()), Op (SetFormat ()) r a impl) => Ref a -> impl #

getFormat :: (HasCallStack, Match r ~ FindOp a a (GetFormat ()), Op (GetFormat ()) r a impl) => Ref a -> impl #

setTabAlign :: (HasCallStack, Match r ~ FindOp a a (SetTabAlign ()), Op (SetTabAlign ()) r a impl) => Ref a -> impl #

getTabAlign :: (HasCallStack, Match r ~ FindOp a a (GetTabAlign ()), Op (GetTabAlign ()) r a impl) => Ref a -> impl #

tabHeight :: (HasCallStack, Match r ~ FindOp a a (TabHeight ()), Op (TabHeight ()) r a impl) => Ref a -> impl #

tabPositions :: (HasCallStack, Match r ~ FindOp a a (TabPositions ()), Op (TabPositions ()) r a impl) => Ref a -> impl #

clientArea :: (HasCallStack, Match r ~ FindOp a a (ClientArea ()), Op (ClientArea ()) r a impl) => Ref a -> impl #

which :: (HasCallStack, Match r ~ FindOp a a (Which ()), Op (Which ()) r a impl) => Ref a -> impl #

setPush :: (HasCallStack, Match r ~ FindOp a a (SetPush ()), Op (SetPush ()) r a impl) => Ref a -> impl #

getPush :: (HasCallStack, Match r ~ FindOp a a (GetPush ()), Op (GetPush ()) r a impl) => Ref a -> impl #

yposition :: (HasCallStack, Match r ~ FindOp a a (Yposition ()), Op (Yposition ()) r a impl) => Ref a -> impl #

xposition :: (HasCallStack, Match r ~ FindOp a a (Xposition ()), Op (Xposition ()) r a impl) => Ref a -> impl #

scrollTo :: (HasCallStack, Match r ~ FindOp a a (ScrollTo ()), Op (ScrollTo ()) r a impl) => Ref a -> impl #

isHorizontal :: (HasCallStack, Match r ~ FindOp a a (IsHorizontal ()), Op (IsHorizontal ()) r a impl) => Ref a -> impl #

getSpacing :: (HasCallStack, Match r ~ FindOp a a (GetSpacing ()), Op (GetSpacing ()) r a impl) => Ref a -> impl #

setSpacing :: (HasCallStack, Match r ~ FindOp a a (SetSpacing ()), Op (SetSpacing ()) r a impl) => Ref a -> impl #

getErrmsg :: (HasCallStack, Match r ~ FindOp a a (GetErrmsg ()), Op (GetErrmsg ()) r a impl) => Ref a -> impl #

getPresetFile :: (HasCallStack, Match r ~ FindOp a a (GetPresetFile ()), Op (GetPresetFile ()) r a impl) => Ref a -> impl #

setPresetFile :: (HasCallStack, Match r ~ FindOp a a (SetPresetFile ()), Op (SetPresetFile ()) r a impl) => Ref a -> impl #

getFilterValue :: (HasCallStack, Match r ~ FindOp a a (GetFilterValue ()), Op (GetFilterValue ()) r a impl) => Ref a -> impl #

setFilterValue :: (HasCallStack, Match r ~ FindOp a a (SetFilterValue ()), Op (SetFilterValue ()) r a impl) => Ref a -> impl #

filters :: (HasCallStack, Match r ~ FindOp a a (Filters ()), Op (Filters ()) r a impl) => Ref a -> impl #

setFilter :: (HasCallStack, Match r ~ FindOp a a (SetFilter ()), Op (SetFilter ()) r a impl) => Ref a -> impl #

getFilter :: (HasCallStack, Match r ~ FindOp a a (GetFilter ()), Op (GetFilter ()) r a impl) => Ref a -> impl #

getTitle :: (HasCallStack, Match r ~ FindOp a a (GetTitle ()), Op (GetTitle ()) r a impl) => Ref a -> impl #

setTitle :: (HasCallStack, Match r ~ FindOp a a (SetTitle ()), Op (SetTitle ()) r a impl) => Ref a -> impl #

getDirectory :: (HasCallStack, Match r ~ FindOp a a (GetDirectory ()), Op (GetDirectory ()) r a impl) => Ref a -> impl #

setDirectory :: (HasCallStack, Match r ~ FindOp a a (SetDirectory ()), Op (SetDirectory ()) r a impl) => Ref a -> impl #

getFilenameAt :: (HasCallStack, Match r ~ FindOp a a (GetFilenameAt ()), Op (GetFilenameAt ()) r a impl) => Ref a -> impl #

getFilename :: (HasCallStack, Match r ~ FindOp a a (GetFilename ()), Op (GetFilename ()) r a impl) => Ref a -> impl #

getOptions :: (HasCallStack, Match r ~ FindOp a a (GetOptions ()), Op (GetOptions ()) r a impl) => Ref a -> impl #

setOptions :: (HasCallStack, Match r ~ FindOp a a (SetOptions ()), Op (SetOptions ()) r a impl) => Ref a -> impl #

getInsertMode :: (HasCallStack, Match r ~ FindOp a a (GetInsertMode ()), Op (GetInsertMode ()) r a impl) => Ref a -> impl #

setInsertMode :: (HasCallStack, Match r ~ FindOp a a (SetInsertMode ()), Op (SetInsertMode ()) r a impl) => Ref a -> impl #

wrapMode :: (HasCallStack, Match r ~ FindOp a a (WrapMode ()), Op (WrapMode ()) r a impl) => Ref a -> impl #

getLinenumberSize :: (HasCallStack, Match r ~ FindOp a a (GetLinenumberSize ()), Op (GetLinenumberSize ()) r a impl) => Ref a -> impl #

setLinenumberSize :: (HasCallStack, Match r ~ FindOp a a (SetLinenumberSize ()), Op (SetLinenumberSize ()) r a impl) => Ref a -> impl #

getLinenumberFont :: (HasCallStack, Match r ~ FindOp a a (GetLinenumberFont ()), Op (GetLinenumberFont ()) r a impl) => Ref a -> impl #

setLinenumberFont :: (HasCallStack, Match r ~ FindOp a a (SetLinenumberFont ()), Op (SetLinenumberFont ()) r a impl) => Ref a -> impl #

colToX :: (HasCallStack, Match r ~ FindOp a a (ColToX ()), Op (ColToX ()) r a impl) => Ref a -> impl #

xToCol :: (HasCallStack, Match r ~ FindOp a a (XToCol ()), Op (XToCol ()) r a impl) => Ref a -> impl #

positionStyle :: (HasCallStack, Match r ~ FindOp a a (PositionStyle ()), Op (PositionStyle ()) r a impl) => Ref a -> impl #

highlightData :: (HasCallStack, Match r ~ FindOp a a (HighlightData ()), Op (HighlightData ()) r a impl) => Ref a -> impl #

setScrollbarAlign :: (HasCallStack, Match r ~ FindOp a a (SetScrollbarAlign ()), Op (SetScrollbarAlign ()) r a impl) => Ref a -> impl #

getScrollbarAlign :: (HasCallStack, Match r ~ FindOp a a (GetScrollbarAlign ()), Op (GetScrollbarAlign ()) r a impl) => Ref a -> impl #

setCursorStyle :: (HasCallStack, Match r ~ FindOp a a (SetCursorStyle ()), Op (SetCursorStyle ()) r a impl) => Ref a -> impl #

showCursor :: (HasCallStack, Match r ~ FindOp a a (ShowCursor ()), Op (ShowCursor ()) r a impl) => Ref a -> impl #

previousWord :: (HasCallStack, Match r ~ FindOp a a (PreviousWord ()), Op (PreviousWord ()) r a impl) => Ref a -> impl #

nextWord :: (HasCallStack, Match r ~ FindOp a a (NextWord ()), Op (NextWord ()) r a impl) => Ref a -> impl #

moveDown :: (HasCallStack, Match r ~ FindOp a a (MoveDown ()), Op (MoveDown ()) r a impl) => Ref a -> impl #

moveUp :: (HasCallStack, Match r ~ FindOp a a (MoveUp ()), Op (MoveUp ()) r a impl) => Ref a -> impl #

moveLeft :: (HasCallStack, Match r ~ FindOp a a (MoveLeft ()), Op (MoveLeft ()) r a impl) => Ref a -> impl #

moveRight :: (HasCallStack, Match r ~ FindOp a a (MoveRight ()), Op (MoveRight ()) r a impl) => Ref a -> impl #

inSelection :: (HasCallStack, Match r ~ FindOp a a (InSelection ()), Op (InSelection ()) r a impl) => Ref a -> impl #

positionToXy :: (HasCallStack, Match r ~ FindOp a a (PositionToXy ()), Op (PositionToXy ()) r a impl) => Ref a -> impl #

xyToPosition :: (HasCallStack, Match r ~ FindOp a a (XyToPosition ()), Op (XyToPosition ()) r a impl) => Ref a -> impl #

getInsertPosition :: (HasCallStack, Match r ~ FindOp a a (GetInsertPosition ()), Op (GetInsertPosition ()) r a impl) => Ref a -> impl #

setInsertPosition :: (HasCallStack, Match r ~ FindOp a a (SetInsertPosition ()), Op (SetInsertPosition ()) r a impl) => Ref a -> impl #

overstrike :: (HasCallStack, Match r ~ FindOp a a (Overstrike ()), Op (Overstrike ()) r a impl) => Ref a -> impl #

scroll :: (HasCallStack, Match r ~ FindOp a a (Scroll ()), Op (Scroll ()) r a impl) => Ref a -> impl #

redisplayRange :: (HasCallStack, Match r ~ FindOp a a (RedisplayRange ()), Op (RedisplayRange ()) r a impl) => Ref a -> impl #

getBuffer :: (HasCallStack, Match r ~ FindOp a a (GetBuffer ()), Op (GetBuffer ()) r a impl) => Ref a -> impl #

setBuffer :: (HasCallStack, Match r ~ FindOp a a (SetBuffer ()), Op (SetBuffer ()) r a impl) => Ref a -> impl #

utf8Align :: (HasCallStack, Match r ~ FindOp a a (Utf8Align ()), Op (Utf8Align ()) r a impl) => Ref a -> impl #

nextCharClipped :: (HasCallStack, Match r ~ FindOp a a (NextCharClipped ()), Op (NextCharClipped ()) r a impl) => Ref a -> impl #

nextChar :: (HasCallStack, Match r ~ FindOp a a (NextChar ()), Op (NextChar ()) r a impl) => Ref a -> impl #

prevCharClipped :: (HasCallStack, Match r ~ FindOp a a (PrevCharClipped ()), Op (PrevCharClipped ()) r a impl) => Ref a -> impl #

prevChar :: (HasCallStack, Match r ~ FindOp a a (PrevChar ()), Op (PrevChar ()) r a impl) => Ref a -> impl #

primarySelection :: (HasCallStack, Match r ~ FindOp a a (PrimarySelection ()), Op (PrimarySelection ()) r a impl) => Ref a -> impl #

findcharBackward :: (HasCallStack, Match r ~ FindOp a a (FindcharBackward ()), Op (FindcharBackward ()) r a impl) => Ref a -> impl #

findcharForward :: (HasCallStack, Match r ~ FindOp a a (FindcharForward ()), Op (FindcharForward ()) r a impl) => Ref a -> impl #

rewindLines :: (HasCallStack, Match r ~ FindOp a a (RewindLines ()), Op (RewindLines ()) r a impl) => Ref a -> impl #

skipLines :: (HasCallStack, Match r ~ FindOp a a (SkipLines ()), Op (SkipLines ()) r a impl) => Ref a -> impl #

countLines :: (HasCallStack, Match r ~ FindOp a a (CountLines ()), Op (CountLines ()) r a impl) => Ref a -> impl #

wordEnd :: (HasCallStack, Match r ~ FindOp a a (WordEnd ()), Op (WordEnd ()) r a impl) => Ref a -> impl #

wordStart :: (HasCallStack, Match r ~ FindOp a a (WordStart ()), Op (WordStart ()) r a impl) => Ref a -> impl #

lineEnd :: (HasCallStack, Match r ~ FindOp a a (LineEnd ()), Op (LineEnd ()) r a impl) => Ref a -> impl #

lineStart :: (HasCallStack, Match r ~ FindOp a a (LineStart ()), Op (LineStart ()) r a impl) => Ref a -> impl #

lineText :: (HasCallStack, Match r ~ FindOp a a (LineText ()), Op (LineText ()) r a impl) => Ref a -> impl #

addModifyCallback :: (HasCallStack, Match r ~ FindOp a a (AddModifyCallback ()), Op (AddModifyCallback ()) r a impl) => Ref a -> impl #

highlightText :: (HasCallStack, Match r ~ FindOp a a (HighlightText ()), Op (HighlightText ()) r a impl) => Ref a -> impl #

highlightPosition :: (HasCallStack, Match r ~ FindOp a a (HighlightPosition ()), Op (HighlightPosition ()) r a impl) => Ref a -> impl #

unhighlight :: (HasCallStack, Match r ~ FindOp a a (Unhighlight ()), Op (Unhighlight ()) r a impl) => Ref a -> impl #

setHighlight :: (HasCallStack, Match r ~ FindOp a a (SetHighlight ()), Op (SetHighlight ()) r a impl) => Ref a -> impl #

getHighlight :: (HasCallStack, Match r ~ FindOp a a (GetHighlight ()), Op (GetHighlight ()) r a impl) => Ref a -> impl #

secondaryUnselect :: (HasCallStack, Match r ~ FindOp a a (SecondaryUnselect ()), Op (SecondaryUnselect ()) r a impl) => Ref a -> impl #

secondarySelected :: (HasCallStack, Match r ~ FindOp a a (SecondarySelected ()), Op (SecondarySelected ()) r a impl) => Ref a -> impl #

secondarySelect :: (HasCallStack, Match r ~ FindOp a a (SecondarySelect ()), Op (SecondarySelect ()) r a impl) => Ref a -> impl #

replaceSelection :: (HasCallStack, Match r ~ FindOp a a (ReplaceSelection ()), Op (ReplaceSelection ()) r a impl) => Ref a -> impl #

removeSelection :: (HasCallStack, Match r ~ FindOp a a (RemoveSelection ()), Op (RemoveSelection ()) r a impl) => Ref a -> impl #

selectionText :: (HasCallStack, Match r ~ FindOp a a (SelectionText ()), Op (SelectionText ()) r a impl) => Ref a -> impl #

selectionPosition :: (HasCallStack, Match r ~ FindOp a a (SelectionPosition ()), Op (SelectionPosition ()) r a impl) => Ref a -> impl #

unselect :: (HasCallStack, Match r ~ FindOp a a (Unselect ()), Op (Unselect ()) r a impl) => Ref a -> impl #

setTabDistance :: (HasCallStack, Match r ~ FindOp a a (SetTabDistance ()), Op (SetTabDistance ()) r a impl) => Ref a -> impl #

getTabDistance :: (HasCallStack, Match r ~ FindOp a a (GetTabDistance ()), Op (GetTabDistance ()) r a impl) => Ref a -> impl #

savefile :: (HasCallStack, Match r ~ FindOp a a (Savefile ()), Op (Savefile ()) r a impl) => Ref a -> impl #

outputfile :: (HasCallStack, Match r ~ FindOp a a (Outputfile ()), Op (Outputfile ()) r a impl) => Ref a -> impl #

loadfile :: (HasCallStack, Match r ~ FindOp a a (Loadfile ()), Op (Loadfile ()) r a impl) => Ref a -> impl #

appendfile :: (HasCallStack, Match r ~ FindOp a a (Appendfile ()), Op (Appendfile ()) r a impl) => Ref a -> impl #

insertfile :: (HasCallStack, Match r ~ FindOp a a (Insertfile ()), Op (Insertfile ()) r a impl) => Ref a -> impl #

canUndo :: (HasCallStack, Match r ~ FindOp a a (CanUndo ()), Op (CanUndo ()) r a impl) => Ref a -> impl #

appendToBuffer :: (HasCallStack, Match r ~ FindOp a a (AppendToBuffer ()), Op (AppendToBuffer ()) r a impl) => Ref a -> impl #

byteAt :: (HasCallStack, Match r ~ FindOp a a (ByteAt ()), Op (ByteAt ()) r a impl) => Ref a -> impl #

charAt :: (HasCallStack, Match r ~ FindOp a a (CharAt ()), Op (CharAt ()) r a impl) => Ref a -> impl #

textRange :: (HasCallStack, Match r ~ FindOp a a (TextRange ()), Op (TextRange ()) r a impl) => Ref a -> impl #

getLength :: (HasCallStack, Match r ~ FindOp a a (GetLength ()), Op (GetLength ()) r a impl) => Ref a -> impl #

includes :: (HasCallStack, Match r ~ FindOp a a (Includes ()), Op (Includes ()) r a impl) => Ref a -> impl #

setSelected :: (HasCallStack, Match r ~ FindOp a a (SetSelected ()), Op (SetSelected ()) r a impl) => Ref a -> impl #

start :: (HasCallStack, Match r ~ FindOp a a (Start ()), Op (Start ()) r a impl) => Ref a -> impl #

update :: (HasCallStack, Match r ~ FindOp a a (Update ()), Op (Update ()) r a impl) => Ref a -> impl #

getItemDrawMode :: (HasCallStack, Match r ~ FindOp a a (GetItemDrawMode ()), Op (GetItemDrawMode ()) r a impl) => Ref a -> impl #

setItemDrawMode :: (HasCallStack, Match r ~ FindOp a a (SetItemDrawMode ()), Op (SetItemDrawMode ()) r a impl) => Ref a -> impl #

getMarginbottom :: (HasCallStack, Match r ~ FindOp a a (GetMarginbottom ()), Op (GetMarginbottom ()) r a impl) => Ref a -> impl #

setMarginbottom :: (HasCallStack, Match r ~ FindOp a a (SetMarginbottom ()), Op (SetMarginbottom ()) r a impl) => Ref a -> impl #

recalcTree :: (HasCallStack, Match r ~ FindOp a a (RecalcTree ()), Op (RecalcTree ()) r a impl) => Ref a -> impl #

getCallbackReason :: (HasCallStack, Match r ~ FindOp a a (GetCallbackReason ()), Op (GetCallbackReason ()) r a impl) => Ref a -> impl #

setCallbackReason :: (HasCallStack, Match r ~ FindOp a a (SetCallbackReason ()), Op (SetCallbackReason ()) r a impl) => Ref a -> impl #

getCallbackItem :: (HasCallStack, Match r ~ FindOp a a (GetCallbackItem ()), Op (GetCallbackItem ()) r a impl) => Ref a -> impl #

setCallbackItem :: (HasCallStack, Match r ~ FindOp a a (SetCallbackItem ()), Op (SetCallbackItem ()) r a impl) => Ref a -> impl #

isVscrollVisible :: (HasCallStack, Match r ~ FindOp a a (IsVscrollVisible ()), Op (IsVscrollVisible ()) r a impl) => Ref a -> impl #

isScrollbar :: (HasCallStack, Match r ~ FindOp a a (IsScrollbar ()), Op (IsScrollbar ()) r a impl) => Ref a -> impl #

setVposition :: (HasCallStack, Match r ~ FindOp a a (SetVposition ()), Op (SetVposition ()) r a impl) => Ref a -> impl #

getVposition :: (HasCallStack, Match r ~ FindOp a a (GetVposition ()), Op (GetVposition ()) r a impl) => Ref a -> impl #

display :: (HasCallStack, Match r ~ FindOp a a (Display ()), Op (Display ()) r a impl) => Ref a -> impl #

showItemBottom :: (HasCallStack, Match r ~ FindOp a a (ShowItemBottom ()), Op (ShowItemBottom ()) r a impl) => Ref a -> impl #

showItemMiddle :: (HasCallStack, Match r ~ FindOp a a (ShowItemMiddle ()), Op (ShowItemMiddle ()) r a impl) => Ref a -> impl #

showItemTop :: (HasCallStack, Match r ~ FindOp a a (ShowItemTop ()), Op (ShowItemTop ()) r a impl) => Ref a -> impl #

showItemWithYoff :: (HasCallStack, Match r ~ FindOp a a (ShowItemWithYoff ()), Op (ShowItemWithYoff ()) r a impl) => Ref a -> impl #

selectmode :: (HasCallStack, Match r ~ FindOp a a (Selectmode ()), Op (Selectmode ()) r a impl) => Ref a -> impl #

setItemLabelfont :: (HasCallStack, Match r ~ FindOp a a (SetItemLabelfont ()), Op (SetItemLabelfont ()) r a impl) => Ref a -> impl #

getItemFocus :: (HasCallStack, Match r ~ FindOp a a (GetItemFocus ()), Op (GetItemFocus ()) r a impl) => Ref a -> impl #

setItemFocus :: (HasCallStack, Match r ~ FindOp a a (SetItemFocus ()), Op (SetItemFocus ()) r a impl) => Ref a -> impl #

selectAndCallback :: (HasCallStack, Match r ~ FindOp a a (SelectAndCallback ()), Op (SelectAndCallback ()) r a impl) => Ref a -> impl #

closeAndCallback :: (HasCallStack, Match r ~ FindOp a a (CloseAndCallback ()), Op (CloseAndCallback ()) r a impl) => Ref a -> impl #

openAndCallback :: (HasCallStack, Match r ~ FindOp a a (OpenAndCallback ()), Op (OpenAndCallback ()) r a impl) => Ref a -> impl #

nextSelectedItem :: (HasCallStack, Match r ~ FindOp a a (NextSelectedItem ()), Op (NextSelectedItem ()) r a impl) => Ref a -> impl #

lastSelectedItem :: (HasCallStack, Match r ~ FindOp a a (LastSelectedItem ()), Op (LastSelectedItem ()) r a impl) => Ref a -> impl #

firstSelectedItem :: (HasCallStack, Match r ~ FindOp a a (FirstSelectedItem ()), Op (FirstSelectedItem ()) r a impl) => Ref a -> impl #

lastVisible :: (HasCallStack, Match r ~ FindOp a a (LastVisible ()), Op (LastVisible ()) r a impl) => Ref a -> impl #

getLast :: (HasCallStack, Match r ~ FindOp a a (GetLast ()), Op (GetLast ()) r a impl) => Ref a -> impl #

prevBeforeItem :: (HasCallStack, Match r ~ FindOp a a (PrevBeforeItem ()), Op (PrevBeforeItem ()) r a impl) => Ref a -> impl #

nextItem :: (HasCallStack, Match r ~ FindOp a a (NextItem ()), Op (NextItem ()) r a impl) => Ref a -> impl #

nextAfterItem :: (HasCallStack, Match r ~ FindOp a a (NextAfterItem ()), Op (NextAfterItem ()) r a impl) => Ref a -> impl #

firstVisible :: (HasCallStack, Match r ~ FindOp a a (FirstVisible ()), Op (FirstVisible ()) r a impl) => Ref a -> impl #

itemClicked :: (HasCallStack, Match r ~ FindOp a a (ItemClicked ()), Op (ItemClicked ()) r a impl) => Ref a -> impl #

root :: (HasCallStack, Match r ~ FindOp a a (Root ()), Op (Root ()) r a impl) => Ref a -> impl #

rootLabel :: (HasCallStack, Match r ~ FindOp a a (RootLabel ()), Op (RootLabel ()) r a impl) => Ref a -> impl #

labelH :: (HasCallStack, Match r ~ FindOp a a (LabelH ()), Op (LabelH ()) r a impl) => Ref a -> impl #

labelW :: (HasCallStack, Match r ~ FindOp a a (LabelW ()), Op (LabelW ()) r a impl) => Ref a -> impl #

labelY :: (HasCallStack, Match r ~ FindOp a a (LabelY ()), Op (LabelY ()) r a impl) => Ref a -> impl #

labelX :: (HasCallStack, Match r ~ FindOp a a (LabelX ()), Op (LabelX ()) r a impl) => Ref a -> impl #

isRoot :: (HasCallStack, Match r ~ FindOp a a (IsRoot ()), Op (IsRoot ()) r a impl) => Ref a -> impl #

eventOnLabel :: (HasCallStack, Match r ~ FindOp a a (EventOnLabel ()), Op (EventOnLabel ()) r a impl) => Ref a -> impl #

findClicked :: (HasCallStack, Match r ~ FindOp a a (FindClicked ()), Op (FindClicked ()) r a impl) => Ref a -> impl #

visibleR :: (HasCallStack, Match r ~ FindOp a a (VisibleR ()), Op (VisibleR ()) r a impl) => Ref a -> impl #

isVisible :: (HasCallStack, Match r ~ FindOp a a (IsVisible ()), Op (IsVisible ()) r a impl) => Ref a -> impl #

isActive :: (HasCallStack, Match r ~ FindOp a a (IsActive ()), Op (IsActive ()) r a impl) => Ref a -> impl #

activateWith :: (HasCallStack, Match r ~ FindOp a a (ActivateWith ()), Op (ActivateWith ()) r a impl) => Ref a -> impl #

deselectAll :: (HasCallStack, Match r ~ FindOp a a (DeselectAll ()), Op (DeselectAll ()) r a impl) => Ref a -> impl #

selectAll :: (HasCallStack, Match r ~ FindOp a a (SelectAll ()), Op (SelectAll ()) r a impl) => Ref a -> impl #

selectToggle :: (HasCallStack, Match r ~ FindOp a a (SelectToggle ()), Op (SelectToggle ()) r a impl) => Ref a -> impl #

selectSet :: (HasCallStack, Match r ~ FindOp a a (SelectSet ()), Op (SelectSet ()) r a impl) => Ref a -> impl #

openToggle :: (HasCallStack, Match r ~ FindOp a a (OpenToggle ()), Op (OpenToggle ()) r a impl) => Ref a -> impl #

isClose :: (HasCallStack, Match r ~ FindOp a a (IsClose ()), Op (IsClose ()) r a impl) => Ref a -> impl #

isOpen :: (HasCallStack, Match r ~ FindOp a a (IsOpen ()), Op (IsOpen ()) r a impl) => Ref a -> impl #

close :: (HasCallStack, Match r ~ FindOp a a (Close ()), Op (Close ()) r a impl) => Ref a -> impl #

open :: (HasCallStack, Match r ~ FindOp a a (Open ()), Op (Open ()) r a impl) => Ref a -> impl #

prevDisplayed :: (HasCallStack, Match r ~ FindOp a a (PrevDisplayed ()), Op (PrevDisplayed ()) r a impl) => Ref a -> impl #

nextDisplayed :: (HasCallStack, Match r ~ FindOp a a (NextDisplayed ()), Op (NextDisplayed ()) r a impl) => Ref a -> impl #

updatePrevNext :: (HasCallStack, Match r ~ FindOp a a (UpdatePrevNext ()), Op (UpdatePrevNext ()) r a impl) => Ref a -> impl #

prevSibling :: (HasCallStack, Match r ~ FindOp a a (PrevSibling ()), Op (PrevSibling ()) r a impl) => Ref a -> impl #

nextSibling :: (HasCallStack, Match r ~ FindOp a a (NextSibling ()), Op (NextSibling ()) r a impl) => Ref a -> impl #

getDepth :: (HasCallStack, Match r ~ FindOp a a (GetDepth ()), Op (GetDepth ()) r a impl) => Ref a -> impl #

moveTo :: (HasCallStack, Match r ~ FindOp a a (MoveTo ()), Op (MoveTo ()) r a impl) => Ref a -> impl #

reparent :: (HasCallStack, Match r ~ FindOp a a (Reparent ()), Op (Reparent ()) r a impl) => Ref a -> impl #

deparent :: (HasCallStack, Match r ~ FindOp a a (Deparent ()), Op (Deparent ()) r a impl) => Ref a -> impl #

insertAbove :: (HasCallStack, Match r ~ FindOp a a (InsertAbove ()), Op (InsertAbove ()) r a impl) => Ref a -> impl #

addAt :: (HasCallStack, Match r ~ FindOp a a (AddAt ()), Op (AddAt ()) r a impl) => Ref a -> impl #

findItem :: (HasCallStack, Match r ~ FindOp a a (FindItem ()), Op (FindItem ()) r a impl) => Ref a -> impl #

findInChildren :: (HasCallStack, Match r ~ FindOp a a (FindInChildren ()), Op (FindInChildren ()) r a impl) => Ref a -> impl #

swapChildren :: (HasCallStack, Match r ~ FindOp a a (SwapChildren ()), Op (SwapChildren ()) r a impl) => Ref a -> impl #

clearChildren :: (HasCallStack, Match r ~ FindOp a a (ClearChildren ()), Op (ClearChildren ()) r a impl) => Ref a -> impl #

removeChild :: (HasCallStack, Match r ~ FindOp a a (RemoveChild ()), Op (RemoveChild ()) r a impl) => Ref a -> impl #

findChild :: (HasCallStack, Match r ~ FindOp a a (FindChild ()), Op (FindChild ()) r a impl) => Ref a -> impl #

hasChildren :: (HasCallStack, Match r ~ FindOp a a (HasChildren ()), Op (HasChildren ()) r a impl) => Ref a -> impl #

child :: (HasCallStack, Match r ~ FindOp a a (Child ()), Op (Child ()) r a impl) => Ref a -> impl #

getWidget :: (HasCallStack, Match r ~ FindOp a a (GetWidget ()), Op (GetWidget ()) r a impl) => Ref a -> impl #

setWidget :: (HasCallStack, Match r ~ FindOp a a (SetWidget ()), Op (SetWidget ()) r a impl) => Ref a -> impl #

showSelf :: (HasCallStack, Match r ~ FindOp a a (ShowSelf ()), Op (ShowSelf ()) r a impl) => Ref a -> impl #

setSelectmode :: (HasCallStack, Match r ~ FindOp a a (SetSelectmode ()), Op (SetSelectmode ()) r a impl) => Ref a -> impl #

getSelectmode :: (HasCallStack, Match r ~ FindOp a a (GetSelectmode ()), Op (GetSelectmode ()) r a impl) => Ref a -> impl #

setShowroot :: (HasCallStack, Match r ~ FindOp a a (SetShowroot ()), Op (SetShowroot ()) r a impl) => Ref a -> impl #

getShowroot :: (HasCallStack, Match r ~ FindOp a a (GetShowroot ()), Op (GetShowroot ()) r a impl) => Ref a -> impl #

setSelectbox :: (HasCallStack, Match r ~ FindOp a a (SetSelectbox ()), Op (SetSelectbox ()) r a impl) => Ref a -> impl #

getSelectbox :: (HasCallStack, Match r ~ FindOp a a (GetSelectbox ()), Op (GetSelectbox ()) r a impl) => Ref a -> impl #

setSortorder :: (HasCallStack, Match r ~ FindOp a a (SetSortorder ()), Op (SetSortorder ()) r a impl) => Ref a -> impl #

getSortorder :: (HasCallStack, Match r ~ FindOp a a (GetSortorder ()), Op (GetSortorder ()) r a impl) => Ref a -> impl #

setShowcollapse :: (HasCallStack, Match r ~ FindOp a a (SetShowcollapse ()), Op (SetShowcollapse ()) r a impl) => Ref a -> impl #

getShowcollapse :: (HasCallStack, Match r ~ FindOp a a (GetShowcollapse ()), Op (GetShowcollapse ()) r a impl) => Ref a -> impl #

setUsericon :: (HasCallStack, Match r ~ FindOp a a (SetUsericon ()), Op (SetUsericon ()) r a impl) => Ref a -> impl #

getUsericon :: (HasCallStack, Match r ~ FindOp a a (GetUsericon ()), Op (GetUsericon ()) r a impl) => Ref a -> impl #

setCloseicon :: (HasCallStack, Match r ~ FindOp a a (SetCloseicon ()), Op (SetCloseicon ()) r a impl) => Ref a -> impl #

getCloseicon :: (HasCallStack, Match r ~ FindOp a a (GetCloseicon ()), Op (GetCloseicon ()) r a impl) => Ref a -> impl #

setOpenicon :: (HasCallStack, Match r ~ FindOp a a (SetOpenicon ()), Op (SetOpenicon ()) r a impl) => Ref a -> impl #

getOpenicon :: (HasCallStack, Match r ~ FindOp a a (GetOpenicon ()), Op (GetOpenicon ()) r a impl) => Ref a -> impl #

setConnectorwidth :: (HasCallStack, Match r ~ FindOp a a (SetConnectorwidth ()), Op (SetConnectorwidth ()) r a impl) => Ref a -> impl #

getConnectorwidth :: (HasCallStack, Match r ~ FindOp a a (GetConnectorwidth ()), Op (GetConnectorwidth ()) r a impl) => Ref a -> impl #

setConnectorstyle :: (HasCallStack, Match r ~ FindOp a a (SetConnectorstyle ()), Op (SetConnectorstyle ()) r a impl) => Ref a -> impl #

getConnectorstyle :: (HasCallStack, Match r ~ FindOp a a (GetConnectorstyle ()), Op (GetConnectorstyle ()) r a impl) => Ref a -> impl #

setConnectorcolor :: (HasCallStack, Match r ~ FindOp a a (SetConnectorcolor ()), Op (SetConnectorcolor ()) r a impl) => Ref a -> impl #

getConnectorcolor :: (HasCallStack, Match r ~ FindOp a a (GetConnectorcolor ()), Op (GetConnectorcolor ()) r a impl) => Ref a -> impl #

setLinespacing :: (HasCallStack, Match r ~ FindOp a a (SetLinespacing ()), Op (SetLinespacing ()) r a impl) => Ref a -> impl #

getLinespacing :: (HasCallStack, Match r ~ FindOp a a (GetLinespacing ()), Op (GetLinespacing ()) r a impl) => Ref a -> impl #

setMargintop :: (HasCallStack, Match r ~ FindOp a a (SetMargintop ()), Op (SetMargintop ()) r a impl) => Ref a -> impl #

getMargintop :: (HasCallStack, Match r ~ FindOp a a (GetMargintop ()), Op (GetMargintop ()) r a impl) => Ref a -> impl #

setMarginleft :: (HasCallStack, Match r ~ FindOp a a (SetMarginleft ()), Op (SetMarginleft ()) r a impl) => Ref a -> impl #

getMarginleft :: (HasCallStack, Match r ~ FindOp a a (GetMarginleft ()), Op (GetMarginleft ()) r a impl) => Ref a -> impl #

setLabelbgcolor :: (HasCallStack, Match r ~ FindOp a a (SetLabelbgcolor ()), Op (SetLabelbgcolor ()) r a impl) => Ref a -> impl #

getLabelbgcolor :: (HasCallStack, Match r ~ FindOp a a (GetLabelbgcolor ()), Op (GetLabelbgcolor ()) r a impl) => Ref a -> impl #

setLabelfgcolor :: (HasCallStack, Match r ~ FindOp a a (SetLabelfgcolor ()), Op (SetLabelfgcolor ()) r a impl) => Ref a -> impl #

getLabelfgcolor :: (HasCallStack, Match r ~ FindOp a a (GetLabelfgcolor ()), Op (GetLabelfgcolor ()) r a impl) => Ref a -> impl #

setItemLabelsize :: (HasCallStack, Match r ~ FindOp a a (SetItemLabelsize ()), Op (SetItemLabelsize ()) r a impl) => Ref a -> impl #

getItemLabelsize :: (HasCallStack, Match r ~ FindOp a a (GetItemLabelsize ()), Op (GetItemLabelsize ()) r a impl) => Ref a -> impl #

getItemLabelfont :: (HasCallStack, Match r ~ FindOp a a (GetItemLabelfont ()), Op (GetItemLabelfont ()) r a impl) => Ref a -> impl #

setShadow :: (HasCallStack, Match r ~ FindOp a a (SetShadow ()), Op (SetShadow ()) r a impl) => Ref a -> impl #

getShadow :: (HasCallStack, Match r ~ FindOp a a (GetShadow ()), Op (GetShadow ()) r a impl) => Ref a -> impl #

sort :: (HasCallStack, Match r ~ FindOp a a (Sort ()), Op (Sort ()) r a impl) => Ref a -> impl #

sortWithSortType :: (HasCallStack, Match r ~ FindOp a a (SortWithSortType ()), Op (SortWithSortType ()) r a impl) => Ref a -> impl #

setScrollbarColor :: (HasCallStack, Match r ~ FindOp a a (SetScrollbarColor ()), Op (SetScrollbarColor ()) r a impl) => Ref a -> impl #

setScrollbarWidth :: (HasCallStack, Match r ~ FindOp a a (SetScrollbarWidth ()), Op (SetScrollbarWidth ()) r a impl) => Ref a -> impl #

getScrollbarWidth :: (HasCallStack, Match r ~ FindOp a a (GetScrollbarWidth ()), Op (GetScrollbarWidth ()) r a impl) => Ref a -> impl #

setScrollbarSize :: (HasCallStack, Match r ~ FindOp a a (SetScrollbarSize ()), Op (SetScrollbarSize ()) r a impl) => Ref a -> impl #

getScrollbarSize :: (HasCallStack, Match r ~ FindOp a a (GetScrollbarSize ()), Op (GetScrollbarSize ()) r a impl) => Ref a -> impl #

setHasScrollbar :: (HasCallStack, Match r ~ FindOp a a (SetHasScrollbar ()), Op (SetHasScrollbar ()) r a impl) => Ref a -> impl #

getHasScrollbar :: (HasCallStack, Match r ~ FindOp a a (GetHasScrollbar ()), Op (GetHasScrollbar ()) r a impl) => Ref a -> impl #

setHposition :: (HasCallStack, Match r ~ FindOp a a (SetHposition ()), Op (SetHposition ()) r a impl) => Ref a -> impl #

getHposition :: (HasCallStack, Match r ~ FindOp a a (GetHposition ()), Op (GetHposition ()) r a impl) => Ref a -> impl #

deselect :: (HasCallStack, Match r ~ FindOp a a (Deselect ()), Op (Deselect ()) r a impl) => Ref a -> impl #

selectOnly :: (HasCallStack, Match r ~ FindOp a a (SelectOnly ()), Op (SelectOnly ()) r a impl) => Ref a -> impl #

removeIcon :: (HasCallStack, Match r ~ FindOp a a (RemoveIcon ()), Op (RemoveIcon ()) r a impl) => Ref a -> impl #

makeVisible :: (HasCallStack, Match r ~ FindOp a a (MakeVisible ()), Op (MakeVisible ()) r a impl) => Ref a -> impl #

displayed :: (HasCallStack, Match r ~ FindOp a a (Displayed ()), Op (Displayed ()) r a impl) => Ref a -> impl #

setColumnWidths :: (HasCallStack, Match r ~ FindOp a a (SetColumnWidths ()), Op (SetColumnWidths ()) r a impl) => Ref a -> impl #

getColumnWidths :: (HasCallStack, Match r ~ FindOp a a (GetColumnWidths ()), Op (GetColumnWidths ()) r a impl) => Ref a -> impl #

setColumnChar :: (HasCallStack, Match r ~ FindOp a a (SetColumnChar ()), Op (SetColumnChar ()) r a impl) => Ref a -> impl #

getColumnChar :: (HasCallStack, Match r ~ FindOp a a (GetColumnChar ()), Op (GetColumnChar ()) r a impl) => Ref a -> impl #

setFormatChar :: (HasCallStack, Match r ~ FindOp a a (SetFormatChar ()), Op (SetFormatChar ()) r a impl) => Ref a -> impl #

getFormatChar :: (HasCallStack, Match r ~ FindOp a a (GetFormatChar ()), Op (GetFormatChar ()) r a impl) => Ref a -> impl #

setText :: (HasCallStack, Match r ~ FindOp a a (SetText ()), Op (SetText ()) r a impl) => Ref a -> impl #

hideLine :: (HasCallStack, Match r ~ FindOp a a (HideLine ()), Op (HideLine ()) r a impl) => Ref a -> impl #

showWidgetLine :: (HasCallStack, Match r ~ FindOp a a (ShowWidgetLine ()), Op (ShowWidgetLine ()) r a impl) => Ref a -> impl #

selected :: (HasCallStack, Match r ~ FindOp a a (Selected ()), Op (Selected ()) r a impl) => Ref a -> impl #

select :: (HasCallStack, Match r ~ FindOp a a (Select ()), Op (Select ()) r a impl) => Ref a -> impl #

setMiddleline :: (HasCallStack, Match r ~ FindOp a a (SetMiddleline ()), Op (SetMiddleline ()) r a impl) => Ref a -> impl #

setBottomline :: (HasCallStack, Match r ~ FindOp a a (SetBottomline ()), Op (SetBottomline ()) r a impl) => Ref a -> impl #

setTopline :: (HasCallStack, Match r ~ FindOp a a (SetTopline ()), Op (SetTopline ()) r a impl) => Ref a -> impl #

lineposition :: (HasCallStack, Match r ~ FindOp a a (Lineposition ()), Op (Lineposition ()) r a impl) => Ref a -> impl #

getTopline :: (HasCallStack, Match r ~ FindOp a a (GetTopline ()), Op (GetTopline ()) r a impl) => Ref a -> impl #

swap :: (HasCallStack, Match r ~ FindOp a a (Swap ()), Op (Swap ()) r a impl) => Ref a -> impl #

load :: (HasCallStack, Match r ~ FindOp a a (Load ()), Op (Load ()) r a impl) => Ref a -> impl #

move :: (HasCallStack, Match r ~ FindOp a a (Move ()), Op (Move ()) r a impl) => Ref a -> impl #

pixelW :: (HasCallStack, Match r ~ FindOp a a (PixelW ()), Op (PixelW ()) r a impl) => Ref a -> impl #

pixelH :: (HasCallStack, Match r ~ FindOp a a (PixelH ()), Op (PixelH ()) r a impl) => Ref a -> impl #

pixelsPerUnit :: (HasCallStack, Match r ~ FindOp a a (PixelsPerUnit ()), Op (PixelsPerUnit ()) r a impl) => Ref a -> impl #

hideOverlay :: (HasCallStack, Match r ~ FindOp a a (HideOverlay ()), Op (HideOverlay ()) r a impl) => Ref a -> impl #

ortho :: (HasCallStack, Match r ~ FindOp a a (Ortho ()), Op (Ortho ()) r a impl) => Ref a -> impl #

swapBuffers :: (HasCallStack, Match r ~ FindOp a a (SwapBuffers ()), Op (SwapBuffers ()) r a impl) => Ref a -> impl #

setContext :: (HasCallStack, Match r ~ FindOp a a (SetContext ()), Op (SetContext ()) r a impl) => Ref a -> impl #

getContext :: (HasCallStack, Match r ~ FindOp a a (GetContext ()), Op (GetContext ()) r a impl) => Ref a -> impl #

canDo :: (HasCallStack, Match r ~ FindOp a a (CanDo ()), Op (CanDo ()) r a impl) => Ref a -> impl #

setContextValid :: (HasCallStack, Match r ~ FindOp a a (SetContextValid ()), Op (SetContextValid ()) r a impl) => Ref a -> impl #

getContextValid :: (HasCallStack, Match r ~ FindOp a a (GetContextValid ()), Op (GetContextValid ()) r a impl) => Ref a -> impl #

invalidate :: (HasCallStack, Match r ~ FindOp a a (Invalidate ()), Op (Invalidate ()) r a impl) => Ref a -> impl #

setValid :: (HasCallStack, Match r ~ FindOp a a (SetValid ()), Op (SetValid ()) r a impl) => Ref a -> impl #

getValid :: (HasCallStack, Match r ~ FindOp a a (GetValid ()), Op (GetValid ()) r a impl) => Ref a -> impl #

selectAllRows :: (HasCallStack, Match r ~ FindOp a a (SelectAllRows ()), Op (SelectAllRows ()) r a impl) => Ref a -> impl #

getRowSelected :: (HasCallStack, Match r ~ FindOp a a (GetRowSelected ()), Op (GetRowSelected ()) r a impl) => Ref a -> impl #

getTabCellNav :: (HasCallStack, Match r ~ FindOp a a (GetTabCellNav ()), Op (GetTabCellNav ()) r a impl) => Ref a -> impl #

setTabCellNav :: (HasCallStack, Match r ~ FindOp a a (SetTabCellNav ()), Op (SetTabCellNav ()) r a impl) => Ref a -> impl #

setColsSuper :: (HasCallStack, Match r ~ FindOp a a (SetColsSuper ()), Op (SetColsSuper ()) r a impl) => Ref a -> impl #

setRowsSuper :: (HasCallStack, Match r ~ FindOp a a (SetRowsSuper ()), Op (SetRowsSuper ()) r a impl) => Ref a -> impl #

clearSuper :: (HasCallStack, Match r ~ FindOp a a (ClearSuper ()), Op (ClearSuper ()) r a impl) => Ref a -> impl #

findCell :: (HasCallStack, Match r ~ FindOp a a (FindCell ()), Op (FindCell ()) r a impl) => Ref a -> impl #

callbackContext :: (HasCallStack, Match r ~ FindOp a a (CallbackContext ()), Op (CallbackContext ()) r a impl) => Ref a -> impl #

callbackCol :: (HasCallStack, Match r ~ FindOp a a (CallbackCol ()), Op (CallbackCol ()) r a impl) => Ref a -> impl #

callbackRow :: (HasCallStack, Match r ~ FindOp a a (CallbackRow ()), Op (CallbackRow ()) r a impl) => Ref a -> impl #

moveCursor :: (HasCallStack, Match r ~ FindOp a a (MoveCursor ()), Op (MoveCursor ()) r a impl) => Ref a -> impl #

setSelection :: (HasCallStack, Match r ~ FindOp a a (SetSelection ()), Op (SetSelection ()) r a impl) => Ref a -> impl #

getSelection :: (HasCallStack, Match r ~ FindOp a a (GetSelection ()), Op (GetSelection ()) r a impl) => Ref a -> impl #

isSelected :: (HasCallStack, Match r ~ FindOp a a (IsSelected ()), Op (IsSelected ()) r a impl) => Ref a -> impl #

getTopRow :: (HasCallStack, Match r ~ FindOp a a (GetTopRow ()), Op (GetTopRow ()) r a impl) => Ref a -> impl #

setTopRow :: (HasCallStack, Match r ~ FindOp a a (SetTopRow ()), Op (SetTopRow ()) r a impl) => Ref a -> impl #

getColPosition :: (HasCallStack, Match r ~ FindOp a a (GetColPosition ()), Op (GetColPosition ()) r a impl) => Ref a -> impl #

getRowPosition :: (HasCallStack, Match r ~ FindOp a a (GetRowPosition ()), Op (GetRowPosition ()) r a impl) => Ref a -> impl #

setColPosition :: (HasCallStack, Match r ~ FindOp a a (SetColPosition ()), Op (SetColPosition ()) r a impl) => Ref a -> impl #

setRowPosition :: (HasCallStack, Match r ~ FindOp a a (SetRowPosition ()), Op (SetRowPosition ()) r a impl) => Ref a -> impl #

setColWidthAll :: (HasCallStack, Match r ~ FindOp a a (SetColWidthAll ()), Op (SetColWidthAll ()) r a impl) => Ref a -> impl #

setRowHeightAll :: (HasCallStack, Match r ~ FindOp a a (SetRowHeightAll ()), Op (SetRowHeightAll ()) r a impl) => Ref a -> impl #

getColWidth :: (HasCallStack, Match r ~ FindOp a a (GetColWidth ()), Op (GetColWidth ()) r a impl) => Ref a -> impl #

setColWidth :: (HasCallStack, Match r ~ FindOp a a (SetColWidth ()), Op (SetColWidth ()) r a impl) => Ref a -> impl #

getRowHeight :: (HasCallStack, Match r ~ FindOp a a (GetRowHeight ()), Op (GetRowHeight ()) r a impl) => Ref a -> impl #

setRowHeight :: (HasCallStack, Match r ~ FindOp a a (SetRowHeight ()), Op (SetRowHeight ()) r a impl) => Ref a -> impl #

getColHeaderColor :: (HasCallStack, Match r ~ FindOp a a (GetColHeaderColor ()), Op (GetColHeaderColor ()) r a impl) => Ref a -> impl #

setColHeaderColor :: (HasCallStack, Match r ~ FindOp a a (SetColHeaderColor ()), Op (SetColHeaderColor ()) r a impl) => Ref a -> impl #

getRowHeaderColor :: (HasCallStack, Match r ~ FindOp a a (GetRowHeaderColor ()), Op (GetRowHeaderColor ()) r a impl) => Ref a -> impl #

setRowHeaderColor :: (HasCallStack, Match r ~ FindOp a a (SetRowHeaderColor ()), Op (SetRowHeaderColor ()) r a impl) => Ref a -> impl #

getRowHeaderWidth :: (HasCallStack, Match r ~ FindOp a a (GetRowHeaderWidth ()), Op (GetRowHeaderWidth ()) r a impl) => Ref a -> impl #

setRowHeaderWidth :: (HasCallStack, Match r ~ FindOp a a (SetRowHeaderWidth ()), Op (SetRowHeaderWidth ()) r a impl) => Ref a -> impl #

setColHeader :: (HasCallStack, Match r ~ FindOp a a (SetColHeader ()), Op (SetColHeader ()) r a impl) => Ref a -> impl #

getColHeader :: (HasCallStack, Match r ~ FindOp a a (GetColHeader ()), Op (GetColHeader ()) r a impl) => Ref a -> impl #

setRowHeader :: (HasCallStack, Match r ~ FindOp a a (SetRowHeader ()), Op (SetRowHeader ()) r a impl) => Ref a -> impl #

getRowHeader :: (HasCallStack, Match r ~ FindOp a a (GetRowHeader ()), Op (GetRowHeader ()) r a impl) => Ref a -> impl #

setRowResizeMin :: (HasCallStack, Match r ~ FindOp a a (SetRowResizeMin ()), Op (SetRowResizeMin ()) r a impl) => Ref a -> impl #

getRowResizeMin :: (HasCallStack, Match r ~ FindOp a a (GetRowResizeMin ()), Op (GetRowResizeMin ()) r a impl) => Ref a -> impl #

setColResizeMin :: (HasCallStack, Match r ~ FindOp a a (SetColResizeMin ()), Op (SetColResizeMin ()) r a impl) => Ref a -> impl #

getColResizeMin :: (HasCallStack, Match r ~ FindOp a a (GetColResizeMin ()), Op (GetColResizeMin ()) r a impl) => Ref a -> impl #

setColResize :: (HasCallStack, Match r ~ FindOp a a (SetColResize ()), Op (SetColResize ()) r a impl) => Ref a -> impl #

getColResize :: (HasCallStack, Match r ~ FindOp a a (GetColResize ()), Op (GetColResize ()) r a impl) => Ref a -> impl #

setRowResize :: (HasCallStack, Match r ~ FindOp a a (SetRowResize ()), Op (SetRowResize ()) r a impl) => Ref a -> impl #

getRowResize :: (HasCallStack, Match r ~ FindOp a a (GetRowResize ()), Op (GetRowResize ()) r a impl) => Ref a -> impl #

getVisibleCells :: (HasCallStack, Match r ~ FindOp a a (GetVisibleCells ()), Op (GetVisibleCells ()) r a impl) => Ref a -> impl #

getCols :: (HasCallStack, Match r ~ FindOp a a (GetCols ()), Op (GetCols ()) r a impl) => Ref a -> impl #

setCols :: (HasCallStack, Match r ~ FindOp a a (SetCols ()), Op (SetCols ()) r a impl) => Ref a -> impl #

getRows :: (HasCallStack, Match r ~ FindOp a a (GetRows ()), Op (GetRows ()) r a impl) => Ref a -> impl #

setRows :: (HasCallStack, Match r ~ FindOp a a (SetRows ()), Op (SetRows ()) r a impl) => Ref a -> impl #

getTableBox :: (HasCallStack, Match r ~ FindOp a a (GetTableBox ()), Op (GetTableBox ()) r a impl) => Ref a -> impl #

setTableBox :: (HasCallStack, Match r ~ FindOp a a (SetTableBox ()), Op (SetTableBox ()) r a impl) => Ref a -> impl #

prev :: (HasCallStack, Match r ~ FindOp a a (Prev ()), Op (Prev ()) r a impl) => Ref a -> impl #

setYstep :: (HasCallStack, Match r ~ FindOp a a (SetYstep ()), Op (SetYstep ()) r a impl) => Ref a -> impl #

setXstep :: (HasCallStack, Match r ~ FindOp a a (SetXstep ()), Op (SetXstep ()) r a impl) => Ref a -> impl #

setYbounds :: (HasCallStack, Match r ~ FindOp a a (SetYbounds ()), Op (SetYbounds ()) r a impl) => Ref a -> impl #

setXbounds :: (HasCallStack, Match r ~ FindOp a a (SetXbounds ()), Op (SetXbounds ()) r a impl) => Ref a -> impl #

getYmaximum :: (HasCallStack, Match r ~ FindOp a a (GetYmaximum ()), Op (GetYmaximum ()) r a impl) => Ref a -> impl #

setYmaximum :: (HasCallStack, Match r ~ FindOp a a (SetYmaximum ()), Op (SetYmaximum ()) r a impl) => Ref a -> impl #

getXmaximum :: (HasCallStack, Match r ~ FindOp a a (GetXmaximum ()), Op (GetXmaximum ()) r a impl) => Ref a -> impl #

setXmaximum :: (HasCallStack, Match r ~ FindOp a a (SetXmaximum ()), Op (SetXmaximum ()) r a impl) => Ref a -> impl #

getYminimum :: (HasCallStack, Match r ~ FindOp a a (GetYminimum ()), Op (GetYminimum ()) r a impl) => Ref a -> impl #

setYminimum :: (HasCallStack, Match r ~ FindOp a a (SetYminimum ()), Op (SetYminimum ()) r a impl) => Ref a -> impl #

getXminimum :: (HasCallStack, Match r ~ FindOp a a (GetXminimum ()), Op (GetXminimum ()) r a impl) => Ref a -> impl #

setXminimum :: (HasCallStack, Match r ~ FindOp a a (SetXminimum ()), Op (SetXminimum ()) r a impl) => Ref a -> impl #

getYvalue :: (HasCallStack, Match r ~ FindOp a a (GetYvalue ()), Op (GetYvalue ()) r a impl) => Ref a -> impl #

setYvalue :: (HasCallStack, Match r ~ FindOp a a (SetYvalue ()), Op (SetYvalue ()) r a impl) => Ref a -> impl #

getXvalue :: (HasCallStack, Match r ~ FindOp a a (GetXvalue ()), Op (GetXvalue ()) r a impl) => Ref a -> impl #

setXvalue :: (HasCallStack, Match r ~ FindOp a a (SetXvalue ()), Op (SetXvalue ()) r a impl) => Ref a -> impl #

drawText :: (HasCallStack, Match r ~ FindOp a a (DrawText ()), Op (DrawText ()) r a impl) => Ref a -> impl #

setTabNav :: (HasCallStack, Match r ~ FindOp a a (SetTabNav ()), Op (SetTabNav ()) r a impl) => Ref a -> impl #

getTabNav :: (HasCallStack, Match r ~ FindOp a a (GetTabNav ()), Op (GetTabNav ()) r a impl) => Ref a -> impl #

setWrap :: (HasCallStack, Match r ~ FindOp a a (SetWrap ()), Op (SetWrap ()) r a impl) => Ref a -> impl #

getWrap :: (HasCallStack, Match r ~ FindOp a a (GetWrap ()), Op (GetWrap ()) r a impl) => Ref a -> impl #

setReadonly :: (HasCallStack, Match r ~ FindOp a a (SetReadonly ()), Op (SetReadonly ()) r a impl) => Ref a -> impl #

getReadonly :: (HasCallStack, Match r ~ FindOp a a (GetReadonly ()), Op (GetReadonly ()) r a impl) => Ref a -> impl #

setInputType :: (HasCallStack, Match r ~ FindOp a a (SetInputType ()), Op (SetInputType ()) r a impl) => Ref a -> impl #

getInputType :: (HasCallStack, Match r ~ FindOp a a (GetInputType ()), Op (GetInputType ()) r a impl) => Ref a -> impl #

setCursorColor :: (HasCallStack, Match r ~ FindOp a a (SetCursorColor ()), Op (SetCursorColor ()) r a impl) => Ref a -> impl #

getCursorColor :: (HasCallStack, Match r ~ FindOp a a (GetCursorColor ()), Op (GetCursorColor ()) r a impl) => Ref a -> impl #

copyCuts :: (HasCallStack, Match r ~ FindOp a a (CopyCuts ()), Op (CopyCuts ()) r a impl) => Ref a -> impl #

undo :: (HasCallStack, Match r ~ FindOp a a (Undo ()), Op (Undo ()) r a impl) => Ref a -> impl #

insertWithLength :: (HasCallStack, Match r ~ FindOp a a (InsertWithLength ()), Op (InsertWithLength ()) r a impl) => Ref a -> impl #

cutRange :: (HasCallStack, Match r ~ FindOp a a (CutRange ()), Op (CutRange ()) r a impl) => Ref a -> impl #

cutFromCursor :: (HasCallStack, Match r ~ FindOp a a (CutFromCursor ()), Op (CutFromCursor ()) r a impl) => Ref a -> impl #

cut :: (HasCallStack, Match r ~ FindOp a a (Cut ()), Op (Cut ()) r a impl) => Ref a -> impl #

setMark :: (HasCallStack, Match r ~ FindOp a a (SetMark ()), Op (SetMark ()) r a impl) => Ref a -> impl #

setPosition :: (HasCallStack, Match r ~ FindOp a a (SetPosition ()), Op (SetPosition ()) r a impl) => Ref a -> impl #

getMark :: (HasCallStack, Match r ~ FindOp a a (GetMark ()), Op (GetMark ()) r a impl) => Ref a -> impl #

getPosition :: (HasCallStack, Match r ~ FindOp a a (GetPosition ()), Op (GetPosition ()) r a impl) => Ref a -> impl #

setMaximumSize :: (HasCallStack, Match r ~ FindOp a a (SetMaximumSize ()), Op (SetMaximumSize ()) r a impl) => Ref a -> impl #

getMaximumSize :: (HasCallStack, Match r ~ FindOp a a (GetMaximumSize ()), Op (GetMaximumSize ()) r a impl) => Ref a -> impl #

index :: (HasCallStack, Match r ~ FindOp a a (Index ()), Op (Index ()) r a impl) => Ref a -> impl #

staticValue :: (HasCallStack, Match r ~ FindOp a a (StaticValue ()), Op (StaticValue ()) r a impl) => Ref a -> impl #

getLinesize :: (HasCallStack, Match r ~ FindOp a a (GetLinesize ()), Op (GetLinesize ()) r a impl) => Ref a -> impl #

setLinesize :: (HasCallStack, Match r ~ FindOp a a (SetLinesize ()), Op (SetLinesize ()) r a impl) => Ref a -> impl #

setLstep :: (HasCallStack, Match r ~ FindOp a a (SetLstep ()), Op (SetLstep ()) r a impl) => Ref a -> impl #

setAngles :: (HasCallStack, Match r ~ FindOp a a (SetAngles ()), Op (SetAngles ()) r a impl) => Ref a -> impl #

setAngle2 :: (HasCallStack, Match r ~ FindOp a a (SetAngle2 ()), Op (SetAngle2 ()) r a impl) => Ref a -> impl #

getAngle2 :: (HasCallStack, Match r ~ FindOp a a (GetAngle2 ()), Op (GetAngle2 ()) r a impl) => Ref a -> impl #

setAngle1 :: (HasCallStack, Match r ~ FindOp a a (SetAngle1 ()), Op (SetAngle1 ()) r a impl) => Ref a -> impl #

getAngle1 :: (HasCallStack, Match r ~ FindOp a a (GetAngle1 ()), Op (GetAngle1 ()) r a impl) => Ref a -> impl #

getSoft :: (HasCallStack, Match r ~ FindOp a a (GetSoft ()), Op (GetSoft ()) r a impl) => Ref a -> impl #

setSoft :: (HasCallStack, Match r ~ FindOp a a (SetSoft ()), Op (SetSoft ()) r a impl) => Ref a -> impl #

getOffscreen :: (HasCallStack, Match r ~ FindOp a a (GetOffscreen ()), Op (GetOffscreen ()) r a impl) => Ref a -> impl #

setOrigin :: (HasCallStack, Match r ~ FindOp a a (SetOrigin ()), Op (SetOrigin ()) r a impl) => Ref a -> impl #

printableRect :: (HasCallStack, Match r ~ FindOp a a (PrintableRect ()), Op (PrintableRect ()) r a impl) => Ref a -> impl #

getOrigin :: (HasCallStack, Match r ~ FindOp a a (GetOrigin ()), Op (GetOrigin ()) r a impl) => Ref a -> impl #

setCurrent :: (HasCallStack, Match r ~ FindOp a a (SetCurrent ()), Op (SetCurrent ()) r a impl) => Ref a -> impl #

getDataSize :: (HasCallStack, Match r ~ FindOp a a (GetDataSize ()), Op (GetDataSize ()) r a impl) => Ref a -> impl #

getDataH :: (HasCallStack, Match r ~ FindOp a a (GetDataH ()), Op (GetDataH ()) r a impl) => Ref a -> impl #

getDataW :: (HasCallStack, Match r ~ FindOp a a (GetDataW ()), Op (GetDataW ()) r a impl) => Ref a -> impl #

scale :: (HasCallStack, Match r ~ FindOp a a (Scale ()), Op (Scale ()) r a impl) => Ref a -> impl #

fail :: (HasCallStack, Match r ~ FindOp a a (Fail ()), Op (Fail ()) r a impl) => Ref a -> impl #

uncache :: (HasCallStack, Match r ~ FindOp a a (Uncache ()), Op (Uncache ()) r a impl) => Ref a -> impl #

drawResize :: (HasCallStack, Match r ~ FindOp a a (DrawResize ()), Op (DrawResize ()) r a impl) => Ref a -> impl #

desaturate :: (HasCallStack, Match r ~ FindOp a a (Desaturate ()), Op (Desaturate ()) r a impl) => Ref a -> impl #

inactive :: (HasCallStack, Match r ~ FindOp a a (Inactive ()), Op (Inactive ()) r a impl) => Ref a -> impl #

colorAverage :: (HasCallStack, Match r ~ FindOp a a (ColorAverage ()), Op (ColorAverage ()) r a impl) => Ref a -> impl #

getCount :: (HasCallStack, Match r ~ FindOp a a (GetCount ()), Op (GetCount ()) r a impl) => Ref a -> impl #

getLd :: (HasCallStack, Match r ~ FindOp a a (GetLd ()), Op (GetLd ()) r a impl) => Ref a -> impl #

getD :: (HasCallStack, Match r ~ FindOp a a (GetD ()), Op (GetD ()) r a impl) => Ref a -> impl #

addAndGetMenuItem :: (HasCallStack, Match r ~ FindOp a a (AddAndGetMenuItem ()), Op (AddAndGetMenuItem ()) r a impl) => Ref a -> impl #

downBox :: (HasCallStack, Match r ~ FindOp a a (DownBox ()), Op (DownBox ()) r a impl) => Ref a -> impl #

setTextcolor :: (HasCallStack, Match r ~ FindOp a a (SetTextcolor ()), Op (SetTextcolor ()) r a impl) => Ref a -> impl #

getTextcolor :: (HasCallStack, Match r ~ FindOp a a (GetTextcolor ()), Op (GetTextcolor ()) r a impl) => Ref a -> impl #

setTextsize :: (HasCallStack, Match r ~ FindOp a a (SetTextsize ()), Op (SetTextsize ()) r a impl) => Ref a -> impl #

getTextsize :: (HasCallStack, Match r ~ FindOp a a (GetTextsize ()), Op (GetTextsize ()) r a impl) => Ref a -> impl #

setTextfont :: (HasCallStack, Match r ~ FindOp a a (SetTextfont ()), Op (SetTextfont ()) r a impl) => Ref a -> impl #

getTextfont :: (HasCallStack, Match r ~ FindOp a a (GetTextfont ()), Op (GetTextfont ()) r a impl) => Ref a -> impl #

getTextWithIndex :: (HasCallStack, Match r ~ FindOp a a (GetTextWithIndex ()), Op (GetTextWithIndex ()) r a impl) => Ref a -> impl #

getText :: (HasCallStack, Match r ~ FindOp a a (GetText ()), Op (GetText ()) r a impl) => Ref a -> impl #

mvalue :: (HasCallStack, Match r ~ FindOp a a (Mvalue ()), Op (Mvalue ()) r a impl) => Ref a -> impl #

getMode :: (HasCallStack, Match r ~ FindOp a a (GetMode ()), Op (GetMode ()) r a impl) => Ref a -> impl #

setMode :: (HasCallStack, Match r ~ FindOp a a (SetMode ()), Op (SetMode ()) r a impl) => Ref a -> impl #

remove :: (HasCallStack, Match r ~ FindOp a a (Remove ()), Op (Remove ()) r a impl) => Ref a -> impl #

replace :: (HasCallStack, Match r ~ FindOp a a (Replace ()), Op (Replace ()) r a impl) => Ref a -> impl #

addName :: (HasCallStack, Match r ~ FindOp a a (AddName ()), Op (AddName ()) r a impl) => Ref a -> impl #

clearSubmenu :: (HasCallStack, Match r ~ FindOp a a (ClearSubmenu ()), Op (ClearSubmenu ()) r a impl) => Ref a -> impl #

setSize :: (HasCallStack, Match r ~ FindOp a a (SetSize ()), Op (SetSize ()) r a impl) => Ref a -> impl #

copy :: (HasCallStack, Match r ~ FindOp a a (Copy ()), Op (Copy ()) r a impl) => Ref a -> impl #

setMenu :: (HasCallStack, Match r ~ FindOp a a (SetMenu ()), Op (SetMenu ()) r a impl) => Ref a -> impl #

getMenu :: (HasCallStack, Match r ~ FindOp a a (GetMenu ()), Op (GetMenu ()) r a impl) => Ref a -> impl #

global :: (HasCallStack, Match r ~ FindOp a a (Global ()), Op (Global ()) r a impl) => Ref a -> impl #

findIndex :: (HasCallStack, Match r ~ FindOp a a (FindIndex ()), Op (FindIndex ()) r a impl) => Ref a -> impl #

picked :: (HasCallStack, Match r ~ FindOp a a (Picked ()), Op (Picked ()) r a impl) => Ref a -> impl #

itemPathname :: (HasCallStack, Match r ~ FindOp a a (ItemPathname ()), Op (ItemPathname ()) r a impl) => Ref a -> impl #

getSize :: (HasCallStack, Match r ~ FindOp a a (GetSize ()), Op (GetSize ()) r a impl) => Ref a -> impl #

doCallback :: (HasCallStack, Match r ~ FindOp a a (DoCallback ()), Op (DoCallback ()) r a impl) => Ref a -> impl #

findShortcut :: (HasCallStack, Match r ~ FindOp a a (FindShortcut ()), Op (FindShortcut ()) r a impl) => Ref a -> impl #

testShortcut :: (HasCallStack, Match r ~ FindOp a a (TestShortcut ()), Op (TestShortcut ()) r a impl) => Ref a -> impl #

popup :: (HasCallStack, Match r ~ FindOp a a (Popup ()), Op (Popup ()) r a impl) => Ref a -> impl #

pulldown :: (HasCallStack, Match r ~ FindOp a a (Pulldown ()), Op (Pulldown ()) r a impl) => Ref a -> impl #

setFlags :: (HasCallStack, Match r ~ FindOp a a (SetFlags ()), Op (SetFlags ()) r a impl) => Ref a -> impl #

getFlags :: (HasCallStack, Match r ~ FindOp a a (GetFlags ()), Op (GetFlags ()) r a impl) => Ref a -> impl #

draw :: (HasCallStack, Match r ~ FindOp a a (Draw ()), Op (Draw ()) r a impl) => Ref a -> impl #

drawWithT :: (HasCallStack, Match r ~ FindOp a a (DrawWithT ()), Op (DrawWithT ()) r a impl) => Ref a -> impl #

measure :: (HasCallStack, Match r ~ FindOp a a (Measure ()), Op (Measure ()) r a impl) => Ref a -> impl #

activevisible :: (HasCallStack, Match r ~ FindOp a a (Activevisible ()), Op (Activevisible ()) r a impl) => Ref a -> impl #

visible :: (HasCallStack, Match r ~ FindOp a a (Visible ()), Op (Visible ()) r a impl) => Ref a -> impl #

radio :: (HasCallStack, Match r ~ FindOp a a (Radio ()), Op (Radio ()) r a impl) => Ref a -> impl #

checkbox :: (HasCallStack, Match r ~ FindOp a a (Checkbox ()), Op (Checkbox ()) r a impl) => Ref a -> impl #

submenu :: (HasCallStack, Match r ~ FindOp a a (Submenu ()), Op (Submenu ()) r a impl) => Ref a -> impl #

getFirst :: (HasCallStack, Match r ~ FindOp a a (GetFirst ()), Op (GetFirst ()) r a impl) => Ref a -> impl #

next :: (HasCallStack, Match r ~ FindOp a a (Next ()), Op (Next ()) r a impl) => Ref a -> impl #

nextWithStep :: (HasCallStack, Match r ~ FindOp a a (NextWithStep ()), Op (NextWithStep ()) r a impl) => Ref a -> impl #

setSlider :: (HasCallStack, Match r ~ FindOp a a (SetSlider ()), Op (SetSlider ()) r a impl) => Ref a -> impl #

getSlider :: (HasCallStack, Match r ~ FindOp a a (GetSlider ()), Op (GetSlider ()) r a impl) => Ref a -> impl #

getSliderSize :: (HasCallStack, Match r ~ FindOp a a (GetSliderSize ()), Op (GetSliderSize ()) r a impl) => Ref a -> impl #

setSliderSize :: (HasCallStack, Match r ~ FindOp a a (SetSliderSize ()), Op (SetSliderSize ()) r a impl) => Ref a -> impl #

scrollvalue :: (HasCallStack, Match r ~ FindOp a a (Scrollvalue ()), Op (Scrollvalue ()) r a impl) => Ref a -> impl #

increment :: (HasCallStack, Match r ~ FindOp a a (Increment ()), Op (Increment ()) r a impl) => Ref a -> impl #

clamp :: (HasCallStack, Match r ~ FindOp a a (Clamp ()), Op (Clamp ()) r a impl) => Ref a -> impl #

round :: (HasCallStack, Match r ~ FindOp a a (Round ()), Op (Round ()) r a impl) => Ref a -> impl #

format :: (HasCallStack, Match r ~ FindOp a a (Format ()), Op (Format ()) r a impl) => Ref a -> impl #

precision :: (HasCallStack, Match r ~ FindOp a a (Precision ()), Op (Precision ()) r a impl) => Ref a -> impl #

getStep :: (HasCallStack, Match r ~ FindOp a a (GetStep ()), Op (GetStep ()) r a impl) => Ref a -> impl #

setStep :: (HasCallStack, Match r ~ FindOp a a (SetStep ()), Op (SetStep ()) r a impl) => Ref a -> impl #

range :: (HasCallStack, Match r ~ FindOp a a (Range ()), Op (Range ()) r a impl) => Ref a -> impl #

setMaximum :: (HasCallStack, Match r ~ FindOp a a (SetMaximum ()), Op (SetMaximum ()) r a impl) => Ref a -> impl #

getMaximum :: (HasCallStack, Match r ~ FindOp a a (GetMaximum ()), Op (GetMaximum ()) r a impl) => Ref a -> impl #

setMinimum :: (HasCallStack, Match r ~ FindOp a a (SetMinimum ()), Op (SetMinimum ()) r a impl) => Ref a -> impl #

getMinimum :: (HasCallStack, Match r ~ FindOp a a (GetMinimum ()), Op (GetMinimum ()) r a impl) => Ref a -> impl #

bounds :: (HasCallStack, Match r ~ FindOp a a (Bounds ()), Op (Bounds ()) r a impl) => Ref a -> impl #

setDownColor :: (HasCallStack, Match r ~ FindOp a a (SetDownColor ()), Op (SetDownColor ()) r a impl) => Ref a -> impl #

getDownColor :: (HasCallStack, Match r ~ FindOp a a (GetDownColor ()), Op (GetDownColor ()) r a impl) => Ref a -> impl #

setDownBox :: (HasCallStack, Match r ~ FindOp a a (SetDownBox ()), Op (SetDownBox ()) r a impl) => Ref a -> impl #

getDownBox :: (HasCallStack, Match r ~ FindOp a a (GetDownBox ()), Op (GetDownBox ()) r a impl) => Ref a -> impl #

setShortcut :: (HasCallStack, Match r ~ FindOp a a (SetShortcut ()), Op (SetShortcut ()) r a impl) => Ref a -> impl #

getShortcut :: (HasCallStack, Match r ~ FindOp a a (GetShortcut ()), Op (GetShortcut ()) r a impl) => Ref a -> impl #

setonly :: (HasCallStack, Match r ~ FindOp a a (Setonly ()), Op (Setonly ()) r a impl) => Ref a -> impl #

set :: (HasCallStack, Match r ~ FindOp a a (Set ()), Op (Set ()) r a impl) => Ref a -> impl #

setValue :: (HasCallStack, Match r ~ FindOp a a (SetValue ()), Op (SetValue ()) r a impl) => Ref a -> impl #

getValue :: (HasCallStack, Match r ~ FindOp a a (GetValue ()), Op (GetValue ()) r a impl) => Ref a -> impl #

flush :: (HasCallStack, Match r ~ FindOp a a (Flush ()), Op (Flush ()) r a impl) => Ref a -> impl #

redrawOverlay :: (HasCallStack, Match r ~ FindOp a a (RedrawOverlay ()), Op (RedrawOverlay ()) r a impl) => Ref a -> impl #

canDoOverlay :: (HasCallStack, Match r ~ FindOp a a (CanDoOverlay ()), Op (CanDoOverlay ()) r a impl) => Ref a -> impl #

waitForExpose :: (HasCallStack, Match r ~ FindOp a a (WaitForExpose ()), Op (WaitForExpose ()) r a impl) => Ref a -> impl #

getDecoratedH :: (HasCallStack, Match r ~ FindOp a a (GetDecoratedH ()), Op (GetDecoratedH ()) r a impl) => Ref a -> impl #

getDecoratedW :: (HasCallStack, Match r ~ FindOp a a (GetDecoratedW ()), Op (GetDecoratedW ()) r a impl) => Ref a -> impl #

setDefaultCursor :: (HasCallStack, Match r ~ FindOp a a (SetDefaultCursor ()), Op (SetDefaultCursor ()) r a impl) => Ref a -> impl #

setCursorWithFgBg :: (HasCallStack, Match r ~ FindOp a a (SetCursorWithFgBg ()), Op (SetCursorWithFgBg ()) r a impl) => Ref a -> impl #

setCursor :: (HasCallStack, Match r ~ FindOp a a (SetCursor ()), Op (SetCursor ()) r a impl) => Ref a -> impl #

makeCurrent :: (HasCallStack, Match r ~ FindOp a a (MakeCurrent ()), Op (MakeCurrent ()) r a impl) => Ref a -> impl #

getYRoot :: (HasCallStack, Match r ~ FindOp a a (GetYRoot ()), Op (GetYRoot ()) r a impl) => Ref a -> impl #

getXRoot :: (HasCallStack, Match r ~ FindOp a a (GetXRoot ()), Op (GetXRoot ()) r a impl) => Ref a -> impl #

iconize :: (HasCallStack, Match r ~ FindOp a a (Iconize ()), Op (Iconize ()) r a impl) => Ref a -> impl #

shown :: (HasCallStack, Match r ~ FindOp a a (Shown ()), Op (Shown ()) r a impl) => Ref a -> impl #

setIcon :: (HasCallStack, Match r ~ FindOp a a (SetIcon ()), Op (SetIcon ()) r a impl) => Ref a -> impl #

getIcon :: (HasCallStack, Match r ~ FindOp a a (GetIcon ()), Op (GetIcon ()) r a impl) => Ref a -> impl #

setXclass :: (HasCallStack, Match r ~ FindOp a a (SetXclass ()), Op (SetXclass ()) r a impl) => Ref a -> impl #

getXclass :: (HasCallStack, Match r ~ FindOp a a (GetXclass ()), Op (GetXclass ()) r a impl) => Ref a -> impl #

setIconlabel :: (HasCallStack, Match r ~ FindOp a a (SetIconlabel ()), Op (SetIconlabel ()) r a impl) => Ref a -> impl #

getIconlabel :: (HasCallStack, Match r ~ FindOp a a (GetIconlabel ()), Op (GetIconlabel ()) r a impl) => Ref a -> impl #

sizeRangeWithArgs :: (HasCallStack, Match r ~ FindOp a a (SizeRangeWithArgs ()), Op (SizeRangeWithArgs ()) r a impl) => Ref a -> impl #

sizeRange :: (HasCallStack, Match r ~ FindOp a a (SizeRange ()), Op (SizeRange ()) r a impl) => Ref a -> impl #

freePosition :: (HasCallStack, Match r ~ FindOp a a (FreePosition ()), Op (FreePosition ()) r a impl) => Ref a -> impl #

hotSpot :: (HasCallStack, Match r ~ FindOp a a (HotSpot ()), Op (HotSpot ()) r a impl) => Ref a -> impl #

getTooltipWindow :: (HasCallStack, Match r ~ FindOp a a (GetTooltipWindow ()), Op (GetTooltipWindow ()) r a impl) => Ref a -> impl #

setTooltipWindow :: (HasCallStack, Match r ~ FindOp a a (SetTooltipWindow ()), Op (SetTooltipWindow ()) r a impl) => Ref a -> impl #

getMenuWindow :: (HasCallStack, Match r ~ FindOp a a (GetMenuWindow ()), Op (GetMenuWindow ()) r a impl) => Ref a -> impl #

setMenuWindow :: (HasCallStack, Match r ~ FindOp a a (SetMenuWindow ()), Op (SetMenuWindow ()) r a impl) => Ref a -> impl #

nonModal :: (HasCallStack, Match r ~ FindOp a a (NonModal ()), Op (NonModal ()) r a impl) => Ref a -> impl #

setNonModal :: (HasCallStack, Match r ~ FindOp a a (SetNonModal ()), Op (SetNonModal ()) r a impl) => Ref a -> impl #

getModal :: (HasCallStack, Match r ~ FindOp a a (GetModal ()), Op (GetModal ()) r a impl) => Ref a -> impl #

setModal :: (HasCallStack, Match r ~ FindOp a a (SetModal ()), Op (SetModal ()) r a impl) => Ref a -> impl #

getOverride :: (HasCallStack, Match r ~ FindOp a a (GetOverride ()), Op (GetOverride ()) r a impl) => Ref a -> impl #

setOverride :: (HasCallStack, Match r ~ FindOp a a (SetOverride ()), Op (SetOverride ()) r a impl) => Ref a -> impl #

getBorder :: (HasCallStack, Match r ~ FindOp a a (GetBorder ()), Op (GetBorder ()) r a impl) => Ref a -> impl #

clearBorder :: (HasCallStack, Match r ~ FindOp a a (ClearBorder ()), Op (ClearBorder ()) r a impl) => Ref a -> impl #

setBorder :: (HasCallStack, Match r ~ FindOp a a (SetBorder ()), Op (SetBorder ()) r a impl) => Ref a -> impl #

fullscreenOff :: (HasCallStack, Match r ~ FindOp a a (FullscreenOff ()), Op (FullscreenOff ()) r a impl) => Ref a -> impl #

makeFullscreen :: (HasCallStack, Match r ~ FindOp a a (MakeFullscreen ()), Op (MakeFullscreen ()) r a impl) => Ref a -> impl #

changed :: (HasCallStack, Match r ~ FindOp a a (Changed ()), Op (Changed ()) r a impl) => Ref a -> impl #

flushSuper :: (HasCallStack, Match r ~ FindOp a a (FlushSuper ()), Op (FlushSuper ()) r a impl) => Ref a -> impl #

handleSuper :: (HasCallStack, Match r ~ FindOp a a (HandleSuper ()), Op (HandleSuper ()) r a impl) => Ref a -> impl #

drawSuper :: (HasCallStack, Match r ~ FindOp a a (DrawSuper ()), Op (DrawSuper ()) r a impl) => Ref a -> impl #

getChild :: (HasCallStack, Match r ~ FindOp a a (GetChild ()), Op (GetChild ()) r a impl) => Ref a -> impl #

getArray :: (HasCallStack, Match r ~ FindOp a a (GetArray ()), Op (GetArray ()) r a impl) => Ref a -> impl #

insertBefore :: (HasCallStack, Match r ~ FindOp a a (InsertBefore ()), Op (InsertBefore ()) r a impl) => Ref a -> impl #

ddfdesignKludge :: (HasCallStack, Match r ~ FindOp a a (DdfdesignKludge ()), Op (DdfdesignKludge ()) r a impl) => Ref a -> impl #

focus :: (HasCallStack, Match r ~ FindOp a a (Focus ()), Op (Focus ()) r a impl) => Ref a -> impl #

clipChildren :: (HasCallStack, Match r ~ FindOp a a (ClipChildren ()), Op (ClipChildren ()) r a impl) => Ref a -> impl #

setClipChildren :: (HasCallStack, Match r ~ FindOp a a (SetClipChildren ()), Op (SetClipChildren ()) r a impl) => Ref a -> impl #

children :: (HasCallStack, Match r ~ FindOp a a (Children ()), Op (Children ()) r a impl) => Ref a -> impl #

initSizes :: (HasCallStack, Match r ~ FindOp a a (InitSizes ()), Op (InitSizes ()) r a impl) => Ref a -> impl #

addResizable :: (HasCallStack, Match r ~ FindOp a a (AddResizable ()), Op (AddResizable ()) r a impl) => Ref a -> impl #

getResizable :: (HasCallStack, Match r ~ FindOp a a (GetResizable ()), Op (GetResizable ()) r a impl) => Ref a -> impl #

setNotResizable :: (HasCallStack, Match r ~ FindOp a a (SetNotResizable ()), Op (SetNotResizable ()) r a impl) => Ref a -> impl #

setResizable :: (HasCallStack, Match r ~ FindOp a a (SetResizable ()), Op (SetResizable ()) r a impl) => Ref a -> impl #

clear :: (HasCallStack, Match r ~ FindOp a a (Clear ()), Op (Clear ()) r a impl) => Ref a -> impl #

removeWidget :: (HasCallStack, Match r ~ FindOp a a (RemoveWidget ()), Op (RemoveWidget ()) r a impl) => Ref a -> impl #

removeIndex :: (HasCallStack, Match r ~ FindOp a a (RemoveIndex ()), Op (RemoveIndex ()) r a impl) => Ref a -> impl #

insert :: (HasCallStack, Match r ~ FindOp a a (Insert ()), Op (Insert ()) r a impl) => Ref a -> impl #

add :: (HasCallStack, Match r ~ FindOp a a (Add ()), Op (Add ()) r a impl) => Ref a -> impl #

find :: (HasCallStack, Match r ~ FindOp a a (Find ()), Op (Find ()) r a impl) => Ref a -> impl #

within :: (HasCallStack, Match r ~ FindOp a a (Within ()), Op (Within ()) r a impl) => Ref a -> impl #

end :: (HasCallStack, Match r ~ FindOp a a (End ()), Op (End ()) r a impl) => Ref a -> impl #

begin :: (HasCallStack, Match r ~ FindOp a a (Begin ()), Op (Begin ()) r a impl) => Ref a -> impl #

updateChild :: (HasCallStack, Match r ~ FindOp a a (UpdateChild ()), Op (UpdateChild ()) r a impl) => Ref a -> impl #

drawOutsideLabel :: (HasCallStack, Match r ~ FindOp a a (DrawOutsideLabel ()), Op (DrawOutsideLabel ()) r a impl) => Ref a -> impl #

drawChildren :: (HasCallStack, Match r ~ FindOp a a (DrawChildren ()), Op (DrawChildren ()) r a impl) => Ref a -> impl #

drawChild :: (HasCallStack, Match r ~ FindOp a a (DrawChild ()), Op (DrawChild ()) r a impl) => Ref a -> impl #

clearFlag :: (HasCallStack, Match r ~ FindOp a a (ClearFlag ()), Op (ClearFlag ()) r a impl) => Ref a -> impl #

setFlag :: (HasCallStack, Match r ~ FindOp a a (SetFlag ()), Op (SetFlag ()) r a impl) => Ref a -> impl #

flags :: (HasCallStack, Match r ~ FindOp a a (Flags ()), Op (Flags ()) r a impl) => Ref a -> impl #

drawFocus :: (HasCallStack, Match r ~ FindOp a a (DrawFocus ()), Op (DrawFocus ()) r a impl) => Ref a -> impl #

drawBackdrop :: (HasCallStack, Match r ~ FindOp a a (DrawBackdrop ()), Op (DrawBackdrop ()) r a impl) => Ref a -> impl #

drawBox :: (HasCallStack, Match r ~ FindOp a a (DrawBox ()), Op (DrawBox ()) r a impl) => Ref a -> impl #

hasCallback :: (HasCallStack, Match r ~ FindOp a a (HasCallback ()), Op (HasCallback ()) r a impl) => Ref a -> impl #

setCallback :: (HasCallStack, Match r ~ FindOp a a (SetCallback ()), Op (SetCallback ()) r a impl) => Ref a -> impl #

getCallback :: (HasCallStack, Match r ~ FindOp a a (GetCallback ()), Op (GetCallback ()) r a impl) => Ref a -> impl #

resize :: (HasCallStack, Match r ~ FindOp a a (Resize ()), Op (Resize ()) r a impl) => Ref a -> impl #

resizeSuper :: (HasCallStack, Match r ~ FindOp a a (ResizeSuper ()), Op (ResizeSuper ()) r a impl) => Ref a -> impl #

getTopWindow :: (HasCallStack, Match r ~ FindOp a a (GetTopWindow ()), Op (GetTopWindow ()) r a impl) => Ref a -> impl #

getWindow :: (HasCallStack, Match r ~ FindOp a a (GetWindow ()), Op (GetWindow ()) r a impl) => Ref a -> impl #

measureLabel :: (HasCallStack, Match r ~ FindOp a a (MeasureLabel ()), Op (MeasureLabel ()) r a impl) => Ref a -> impl #

setDamageInside :: (HasCallStack, Match r ~ FindOp a a (SetDamageInside ()), Op (SetDamageInside ()) r a impl) => Ref a -> impl #

setDamage :: (HasCallStack, Match r ~ FindOp a a (SetDamage ()), Op (SetDamage ()) r a impl) => Ref a -> impl #

clearDamage :: (HasCallStack, Match r ~ FindOp a a (ClearDamage ()), Op (ClearDamage ()) r a impl) => Ref a -> impl #

getDamage :: (HasCallStack, Match r ~ FindOp a a (GetDamage ()), Op (GetDamage ()) r a impl) => Ref a -> impl #

redrawLabel :: (HasCallStack, Match r ~ FindOp a a (RedrawLabel ()), Op (RedrawLabel ()) r a impl) => Ref a -> impl #

redraw :: (HasCallStack, Match r ~ FindOp a a (Redraw ()), Op (Redraw ()) r a impl) => Ref a -> impl #

inside :: (HasCallStack, Match r ~ FindOp a a (Inside ()), Op (Inside ()) r a impl) => Ref a -> impl #

contains :: (HasCallStack, Match r ~ FindOp a a (Contains ()), Op (Contains ()) r a impl) => Ref a -> impl #

getVisibleFocus :: (HasCallStack, Match r ~ FindOp a a (GetVisibleFocus ()), Op (GetVisibleFocus ()) r a impl) => Ref a -> impl #

clearVisibleFocus :: (HasCallStack, Match r ~ FindOp a a (ClearVisibleFocus ()), Op (ClearVisibleFocus ()) r a impl) => Ref a -> impl #

setVisibleFocus :: (HasCallStack, Match r ~ FindOp a a (SetVisibleFocus ()), Op (SetVisibleFocus ()) r a impl) => Ref a -> impl #

takeFocus :: (HasCallStack, Match r ~ FindOp a a (TakeFocus ()), Op (TakeFocus ()) r a impl) => Ref a -> impl #

clearActive :: (HasCallStack, Match r ~ FindOp a a (ClearActive ()), Op (ClearActive ()) r a impl) => Ref a -> impl #

setActive :: (HasCallStack, Match r ~ FindOp a a (SetActive ()), Op (SetActive ()) r a impl) => Ref a -> impl #

clearChanged :: (HasCallStack, Match r ~ FindOp a a (ClearChanged ()), Op (ClearChanged ()) r a impl) => Ref a -> impl #

setChanged :: (HasCallStack, Match r ~ FindOp a a (SetChanged ()), Op (SetChanged ()) r a impl) => Ref a -> impl #

takesevents :: (HasCallStack, Match r ~ FindOp a a (Takesevents ()), Op (Takesevents ()) r a impl) => Ref a -> impl #

clearOutput :: (HasCallStack, Match r ~ FindOp a a (ClearOutput ()), Op (ClearOutput ()) r a impl) => Ref a -> impl #

setOutput :: (HasCallStack, Match r ~ FindOp a a (SetOutput ()), Op (SetOutput ()) r a impl) => Ref a -> impl #

getOutput :: (HasCallStack, Match r ~ FindOp a a (GetOutput ()), Op (GetOutput ()) r a impl) => Ref a -> impl #

deactivate :: (HasCallStack, Match r ~ FindOp a a (Deactivate ()), Op (Deactivate ()) r a impl) => Ref a -> impl #

activate :: (HasCallStack, Match r ~ FindOp a a (Activate ()), Op (Activate ()) r a impl) => Ref a -> impl #

activeR :: (HasCallStack, Match r ~ FindOp a a (ActiveR ()), Op (ActiveR ()) r a impl) => Ref a -> impl #

active :: (HasCallStack, Match r ~ FindOp a a (Active ()), Op (Active ()) r a impl) => Ref a -> impl #

clearVisible :: (HasCallStack, Match r ~ FindOp a a (ClearVisible ()), Op (ClearVisible ()) r a impl) => Ref a -> impl #

setVisible :: (HasCallStack, Match r ~ FindOp a a (SetVisible ()), Op (SetVisible ()) r a impl) => Ref a -> impl #

hide :: (HasCallStack, Match r ~ FindOp a a (Hide ()), Op (Hide ()) r a impl) => Ref a -> impl #

hideSuper :: (HasCallStack, Match r ~ FindOp a a (HideSuper ()), Op (HideSuper ()) r a impl) => Ref a -> impl #

showWidget :: (HasCallStack, Match r ~ FindOp a a (ShowWidget ()), Op (ShowWidget ()) r a impl) => Ref a -> impl #

showWidgetSuper :: (HasCallStack, Match r ~ FindOp a a (ShowWidgetSuper ()), Op (ShowWidgetSuper ()) r a impl) => Ref a -> impl #

getVisibleR :: (HasCallStack, Match r ~ FindOp a a (GetVisibleR ()), Op (GetVisibleR ()) r a impl) => Ref a -> impl #

getVisible :: (HasCallStack, Match r ~ FindOp a a (GetVisible ()), Op (GetVisible ()) r a impl) => Ref a -> impl #

setWhen :: (HasCallStack, Match r ~ FindOp a a (SetWhen ()), Op (SetWhen ()) r a impl) => Ref a -> impl #

getWhen :: (HasCallStack, Match r ~ FindOp a a (GetWhen ()), Op (GetWhen ()) r a impl) => Ref a -> impl #

setTooltip :: (HasCallStack, Match r ~ FindOp a a (SetTooltip ()), Op (SetTooltip ()) r a impl) => Ref a -> impl #

copyTooltip :: (HasCallStack, Match r ~ FindOp a a (CopyTooltip ()), Op (CopyTooltip ()) r a impl) => Ref a -> impl #

getTooltip :: (HasCallStack, Match r ~ FindOp a a (GetTooltip ()), Op (GetTooltip ()) r a impl) => Ref a -> impl #

setDeimage :: (HasCallStack, Match r ~ FindOp a a (SetDeimage ()), Op (SetDeimage ()) r a impl) => Ref a -> impl #

getDeimage :: (HasCallStack, Match r ~ FindOp a a (GetDeimage ()), Op (GetDeimage ()) r a impl) => Ref a -> impl #

setImage :: (HasCallStack, Match r ~ FindOp a a (SetImage ()), Op (SetImage ()) r a impl) => Ref a -> impl #

getImage :: (HasCallStack, Match r ~ FindOp a a (GetImage ()), Op (GetImage ()) r a impl) => Ref a -> impl #

setLabelsize :: (HasCallStack, Match r ~ FindOp a a (SetLabelsize ()), Op (SetLabelsize ()) r a impl) => Ref a -> impl #

getLabelsize :: (HasCallStack, Match r ~ FindOp a a (GetLabelsize ()), Op (GetLabelsize ()) r a impl) => Ref a -> impl #

setLabelfont :: (HasCallStack, Match r ~ FindOp a a (SetLabelfont ()), Op (SetLabelfont ()) r a impl) => Ref a -> impl #

getLabelfont :: (HasCallStack, Match r ~ FindOp a a (GetLabelfont ()), Op (GetLabelfont ()) r a impl) => Ref a -> impl #

setLabelcolor :: (HasCallStack, Match r ~ FindOp a a (SetLabelcolor ()), Op (SetLabelcolor ()) r a impl) => Ref a -> impl #

getLabelcolor :: (HasCallStack, Match r ~ FindOp a a (GetLabelcolor ()), Op (GetLabelcolor ()) r a impl) => Ref a -> impl #

setLabeltype :: (HasCallStack, Match r ~ FindOp a a (SetLabeltype ()), Op (SetLabeltype ()) r a impl) => Ref a -> impl #

getLabeltype :: (HasCallStack, Match r ~ FindOp a a (GetLabeltype ()), Op (GetLabeltype ()) r a impl) => Ref a -> impl #

setLabel :: (HasCallStack, Match r ~ FindOp a a (SetLabel ()), Op (SetLabel ()) r a impl) => Ref a -> impl #

copyLabel :: (HasCallStack, Match r ~ FindOp a a (CopyLabel ()), Op (CopyLabel ()) r a impl) => Ref a -> impl #

getLabel :: (HasCallStack, Match r ~ FindOp a a (GetLabel ()), Op (GetLabel ()) r a impl) => Ref a -> impl #

setSelectionColor :: (HasCallStack, Match r ~ FindOp a a (SetSelectionColor ()), Op (SetSelectionColor ()) r a impl) => Ref a -> impl #

getSelectionColor :: (HasCallStack, Match r ~ FindOp a a (GetSelectionColor ()), Op (GetSelectionColor ()) r a impl) => Ref a -> impl #

setColorWithBgSel :: (HasCallStack, Match r ~ FindOp a a (SetColorWithBgSel ()), Op (SetColorWithBgSel ()) r a impl) => Ref a -> impl #

setColor :: (HasCallStack, Match r ~ FindOp a a (SetColor ()), Op (SetColor ()) r a impl) => Ref a -> impl #

getColor :: (HasCallStack, Match r ~ FindOp a a (GetColor ()), Op (GetColor ()) r a impl) => Ref a -> impl #

setBox :: (HasCallStack, Match r ~ FindOp a a (SetBox ()), Op (SetBox ()) r a impl) => Ref a -> impl #

getBox :: (HasCallStack, Match r ~ FindOp a a (GetBox ()), Op (GetBox ()) r a impl) => Ref a -> impl #

getAlign :: (HasCallStack, Match r ~ FindOp a a (GetAlign ()), Op (GetAlign ()) r a impl) => Ref a -> impl #

setAlign :: (HasCallStack, Match r ~ FindOp a a (SetAlign ()), Op (SetAlign ()) r a impl) => Ref a -> impl #

getRectangle :: (HasCallStack, Match r ~ FindOp a a (GetRectangle ()), Op (GetRectangle ()) r a impl) => Ref a -> impl #

getH :: (HasCallStack, Match r ~ FindOp a a (GetH ()), Op (GetH ()) r a impl) => Ref a -> impl #

getW :: (HasCallStack, Match r ~ FindOp a a (GetW ()), Op (GetW ()) r a impl) => Ref a -> impl #

getY :: (HasCallStack, Match r ~ FindOp a a (GetY ()), Op (GetY ()) r a impl) => Ref a -> impl #

getX :: (HasCallStack, Match r ~ FindOp a a (GetX ()), Op (GetX ()) r a impl) => Ref a -> impl #

drawLabel :: (HasCallStack, Match r ~ FindOp a a (DrawLabel ()), Op (DrawLabel ()) r a impl) => Ref a -> impl #

setType :: (HasCallStack, Match r ~ FindOp a a (SetType ()), Op (SetType ()) r a impl) => Ref a -> impl #

getType_ :: (HasCallStack, Match r ~ FindOp a a (GetType_ ()), Op (GetType_ ()) r a impl) => Ref a -> impl #

setParent :: (HasCallStack, Match r ~ FindOp a a (SetParent ()), Op (SetParent ()) r a impl) => Ref a -> impl #

getParent :: (HasCallStack, Match r ~ FindOp a a (GetParent ()), Op (GetParent ()) r a impl) => Ref a -> impl #

handle :: (HasCallStack, Match r ~ FindOp a a (Handle ()), Op (Handle ()) r a impl) => Ref a -> impl #

destroy :: (HasCallStack, Match r ~ FindOp a a (Destroy ()), Op (Destroy ()) r a impl) => Ref a -> impl #

type WidgetBase = CWidgetBase Base #

type Widget = CWidget WidgetBase #

data Destroy a #

data Handle a #

data GetParent a #

data SetParent a #

data GetType_ a #

data SetType a #

data DrawLabel a #

data GetX a #

data GetY a #

data GetW a #

data GetH a #

data SetAlign a #

data GetAlign a #

data GetBox a #

data SetBox a #

data GetColor a #

data SetColor a #

data GetLabel a #

data CopyLabel a #

data SetLabel a #

data GetImage a #

data SetImage a #

data GetDeimage a #

data SetDeimage a #

data GetTooltip a #

data CopyTooltip a #

data SetTooltip a #

data GetWhen a #

data SetWhen a #

data GetVisible a #

data GetVisibleR a #

data ShowWidget a #

data HideSuper a #

data Hide a #

data SetVisible a #

data Active a #

data ActiveR a #

data Activate a #

data Deactivate a #

data GetOutput a #

data SetOutput a #

data ClearOutput a #

data Takesevents a #

data SetChanged a #

data SetActive a #

data ClearActive a #

data TakeFocus a #

data Contains a #

data Inside a #

data Redraw a #

data RedrawLabel a #

data GetDamage a #

data ClearDamage a #

data SetDamage a #

data GetWindow a #

data ResizeSuper a #

data Resize a #

data GetCallback a #

data SetCallback a #

data HasCallback a #

data DrawBox a #

data DrawFocus a #

data Flags a #

data SetFlag a #

data ClearFlag a #

type GroupBase = CGroupBase WidgetBase #

type Group = CGroup GroupBase #

data DrawChild a #

data UpdateChild a #

data Begin a #

data End a #

data Within a #

data Find a #

data Add a #

data Insert a #

data RemoveIndex a #

data Clear a #

data InitSizes a #

data Children a #

data Focus a #

data GetArray a #

data GetChild a #

type WindowBase = CWindowBase GroupBase #

type Window = CWindow WindowBase #

data DrawSuper a #

data HandleSuper a #

data FlushSuper a #

data Changed a #

data SetBorder a #

data ClearBorder a #

data GetBorder a #

data SetOverride a #

data GetOverride a #

data SetModal a #

data GetModal a #

data SetNonModal a #

data NonModal a #

data HotSpot a #

data SizeRange a #

data GetXclass a #

data SetXclass a #

data GetIcon a #

data SetIcon a #

data Shown a #

data Iconize a #

data GetXRoot a #

data GetYRoot a #

data MakeCurrent a #

data SetCursor a #

type SingleWindowBase = CSingleWindowBase WindowBase #

type SingleWindow = CSingleWindow SingleWindowBase #

type DoubleWindowBase = CDoubleWindowBase WindowBase #

type DoubleWindow = CDoubleWindow WindowBase #

type OverlayWindowBase = COverlayWindowBase DoubleWindowBase #

type OverlayWindow = COverlayWindow OverlayWindowBase #

data Flush a #

type ButtonBase = CButtonBase WidgetBase #

type Button = CButton ButtonBase #

data GetValue a #

data SetValue a #

data Set a #

data Setonly a #

data GetShortcut a #

data SetShortcut a #

data GetDownBox a #

data SetDownBox a #

type LightButtonBase = CLightButtonBase ButtonBase #

type LightButton = CLightButton LightButtonBase #

type RadioLightButtonBase = CRadioLightButtonBase LightButtonBase #

type RadioLightButton = CRadioLightButton RadioLightButtonBase #

type CheckButtonBase = CCheckButtonBase LightButtonBase #

type CheckButton = CCheckButton CheckButtonBase #

type ReturnButtonBase = CReturnButtonBase ButtonBase #

type ReturnButton = CReturnButton ReturnButtonBase #

type RoundButtonBase = CRoundButtonBase ButtonBase #

type RoundButton = CRoundButton RoundButtonBase #

type RepeatButtonBase = CRepeatButtonBase ButtonBase #

type RepeatButton = CRepeatButton RepeatButtonBase #

type ToggleButtonBase = CToggleButtonBase ButtonBase #

type ToggleButton = CToggleButton ToggleButtonBase #

type ValuatorBase = CValuatorBase WidgetBase #

type Valuator = CValuator ValuatorBase #

data Bounds a #

data GetMinimum a #

data SetMinimum a #

data GetMaximum a #

data SetMaximum a #

data Range a #

data SetStep a #

data GetStep a #

data Precision a #

data Format a #

data Round a #

data Clamp a #

data Increment a #

type SliderBase = CSliderBase ValuatorBase #

type Slider = CSlider SliderBase #

data Scrollvalue a #

data GetSlider a #

data SetSlider a #

type FillSliderBase = CFillSliderBase SliderBase #

type FillSlider = CFillSlider SliderBase #

type HorSliderBase = CHorSliderBase SliderBase #

type HorSlider = CHorSlider HorSliderBase #

type HorFillSliderBase = CHorFillSliderBase SliderBase #

type HorFillSlider = CHorFillSlider HorFillSliderBase #

type NiceSliderBase = CNiceSliderBase SliderBase #

type NiceSlider = CNiceSlider NiceSliderBase #

type HorNiceSliderBase = CHorNiceSliderBase SliderBase #

type HorNiceSlider = CHorNiceSlider HorNiceSliderBase #

type MenuItemBase = CMenuItemBase Base #

type MenuItem = CMenuItem MenuItemBase #

data Next a #

data GetFirst a #

data Submenu a #

data Checkbox a #

data Radio a #

data Visible a #

data Measure a #

data DrawWithT a #

data Draw a #

data GetFlags a #

data SetFlags a #

data Pulldown a #

data Popup a #

data DoCallback a #

data GetSize a #

type MenuPrimBase = CMenuPrimBase WidgetBase #

type MenuPrim = CMenuPrim MenuPrimBase #

data Picked a #

data FindIndex a #

data Global a #

data GetMenu a #

data SetMenu a #

data Copy a #

data SetSize a #

data AddName a #

data Replace a #

data Remove a #

data SetMode a #

data GetMode a #

data Mvalue a #

data GetText a #

data GetTextfont a #

data SetTextfont a #

data GetTextsize a #

data SetTextsize a #

data DownBox a #

type MenuBarBase = CMenuBarBase MenuPrimBase #

type MenuBar = CMenuBar MenuBarBase #

type SysMenuBarBase = CSysMenuBarBase MenuBarBase #

type SysMenuBar = CSysMenuBar SysMenuBarBase #

type ChoiceBase = CChoiceBase MenuPrimBase #

type Choice = CChoice ChoiceBase #

type MenuButtonBase = CMenuButtonBase MenuPrimBase #

type MenuButton = CMenuButton MenuButtonBase #

type Image = CImage Base #

data GetD a #

data GetLd a #

data GetCount a #

data Inactive a #

data Desaturate a #

data DrawResize a #

data Uncache a #

data Fail a #

data Scale a #

data GetDataW a #

data GetDataH a #

data GetDataSize a #

type Bitmap = CBitmap Image #

type Pixmap = CPixmap Image #

type CopySurface = CCopySurface Base #

data SetCurrent a #

type ImageSurface = CImageSurface Base #

data GetOrigin a #

data SetOrigin a #

type AdjusterBase = CAdjusterBase ValuatorBase #

type Adjuster = CAdjuster AdjusterBase #

data SetSoft a #

data GetSoft a #

type DialBase = CDialBase ValuatorBase #

type Dial = CDial DialBase #

data GetAngle1 a #

data SetAngle1 a #

data GetAngle2 a #

data SetAngle2 a #

data SetAngles a #

type FillDial = CFillDial DialBase #

type LineDial = CLineDial DialBase #

type RollerBase = CRollerBase ValuatorBase #

type Roller = CRoller RollerBase #

type CounterBase = CCounterBase ValuatorBase #

data SetLstep a #

type Counter = CCounter CounterBase #

type ScrollbarBase = CScrollbarBase SliderBase #

type Scrollbar = CScrollbar ScrollbarBase #

data SetLinesize a #

data GetLinesize a #

type ValueSliderBase = CValueSliderBase SliderBase #

type ValueSlider = CValueSlider ValueSliderBase #

type HorValueSlider = CHorValueSlider ValueSliderBase #

type InputBase = CInputBase WidgetBase #

type Input = CInput InputBase #

data StaticValue a #

data Index a #

data GetPosition a #

data GetMark a #

data SetPosition a #

data SetMark a #

data Cut a #

data CutRange a #

data Undo a #

data CopyCuts a #

data GetReadonly a #

data SetReadonly a #

data GetWrap a #

data SetWrap a #

data GetTabNav a #

data SetTabNav a #

data DrawText a #

type OutputBase = COutputBase InputBase #

type Output = COutput OutputBase #

type ValueInputBase = CValueInputBase ValuatorBase #

type ValueInput = CValueInput ValueInputBase #

type ValueOutputBase = CValueOutputBase ValuatorBase #

type ValueOutput = CValueOutput ValueOutputBase #

type ProgressBase = CProgressBase WidgetBase #

type Progress = CProgress ProgressBase #

type PositionerBase = CPositionerBase WidgetBase #

type Positioner = CPositioner PositionerBase #

data SetXvalue a #

data GetXvalue a #

data SetYvalue a #

data GetYvalue a #

data SetXminimum a #

data GetXminimum a #

data SetYminimum a #

data GetYminimum a #

data SetXmaximum a #

data GetXmaximum a #

data SetYmaximum a #

data GetYmaximum a #

data SetXbounds a #

data SetYbounds a #

data SetXstep a #

data SetYstep a #

type WizardBase = CWizardBase GroupBase #

type Wizard = CWizard WizardBase #

data Prev a #

type TableBase = CTableBase GroupBase #

type Table = CTable TableBase #

data SetTableBox a #

data GetTableBox a #

data SetRows a #

data GetRows a #

data SetCols a #

data GetCols a #

data SetColWidth a #

data GetColWidth a #

data SetTopRow a #

data GetTopRow a #

data IsSelected a #

data MoveCursor a #

data CallbackRow a #

data CallbackCol a #

data FindCell a #

data ClearSuper a #

type TableRowBase = CTableRowBase TableBase #

type TableRow = CTableRow TableRowBase #

type GlWindowBase = CGlWindowBase WindowBase #

type GlWindow = CGlWindow GlWindowBase #

data GetValid a #

data SetValid a #

data Invalidate a #

data CanDo a #

data GetContext a #

data SetContext a #

data SwapBuffers a #

data Ortho a #

data HideOverlay a #

data PixelH a #

data PixelW a #

type Box = CBox WidgetBase #

type BrowserBase = CBrowserBase GroupBase #

type Browser = CBrowser BrowserBase #

data Move a #

data Load a #

data Swap a #

data GetTopline a #

data SetTopline a #

data Select a #

data Selected a #

data HideLine a #

data SetText a #

data Displayed a #

data MakeVisible a #

data RemoveIcon a #

data SelectOnly a #

data Deselect a #

data Sort a #

type SelectBrowser = CSelectBrowser BrowserBase #

type IntInput = CIntInput InputBase #

type ClockBase = CClockBase WidgetBase #

type Clock = CClock ClockBase #

data GetShadow a #

data SetShadow a #

type TreePrefs = CTreePrefs Base #

data GetOpenicon a #

data SetOpenicon a #

data GetUsericon a #

data SetUsericon a #

data GetShowroot a #

data SetShowroot a #

type TreeItem = CTreeItem Base #

data ShowSelf a #

data SetWidget a #

data GetWidget a #

data Child a #

data HasChildren a #

data FindChild a #

data RemoveChild a #

data FindItem a #

data AddAt a #

data InsertAbove a #

data Deparent a #

data Reparent a #

data MoveTo a #

data GetDepth a #

data NextSibling a #

data PrevSibling a #

data Open a #

data Close a #

data IsOpen a #

data IsClose a #

data OpenToggle a #

data SelectSet a #

data SelectAll a #

data DeselectAll a #

data IsActive a #

data IsVisible a #

data VisibleR a #

data FindClicked a #

data IsRoot a #

data LabelX a #

data LabelY a #

data LabelW a #

data LabelH a #

type TreeBase = CTreeBase GroupBase #

type Tree = CTree TreeBase #

data RootLabel a #

data Root a #

data ItemClicked a #

data NextItem a #

data GetLast a #

data LastVisible a #

data Selectmode a #

data ShowItemTop a #

data Display a #

data IsScrollbar a #

data RecalcTree a #

type TextSelection = CTextSelection Base #

data Update a #

data Start a #

data SetSelected a #

data Includes a #

type TextBuffer = CTextBuffer Base #

data GetLength a #

data TextRange a #

data CharAt a #

data ByteAt a #

data CanUndo a #

data Insertfile a #

data Appendfile a #

data Loadfile a #

data Outputfile a #

data Savefile a #

data Unselect a #

data Unhighlight a #

data LineText a #

data LineStart a #

data LineEnd a #

data WordStart a #

data WordEnd a #

data CountLines a #

data SkipLines a #

data RewindLines a #

data PrevChar a #

data NextChar a #

data Utf8Align a #

type TextDisplayBase = CTextDisplayBase GroupBase #

type TextDisplay = CTextDisplay TextDisplayBase #

data SetBuffer a #

data GetBuffer a #

data Scroll a #

data Overstrike a #

data InSelection a #

data MoveRight a #

data MoveLeft a #

data MoveUp a #

data MoveDown a #

data NextWord a #

data ShowCursor a #

data XToCol a #

data ColToX a #

data WrapMode a #

type TextEditorBase = CTextEditorBase TextDisplayBase #

type TextEditor = CTextEditor TextEditorBase #

type NativeFileChooser = CNativeFileChooser Base #

data SetOptions a #

data GetOptions a #

data GetFilename a #

data SetTitle a #

data GetTitle a #

data GetFilter a #

data SetFilter a #

data Filters a #

data GetErrmsg a #

type TileBase = CTileBase GroupBase #

type Tile = CTile TileBase #

type PackBase = CPackBase GroupBase #

type Pack = CPack PackBase #

data SetSpacing a #

data GetSpacing a #

type ScrolledBase = CScrolledBase GroupBase #

type Scrolled = CScrolled Group #

data ScrollTo a #

data Xposition a #

data Yposition a #

type TabsBase = CTabsBase GroupBase #

type Tabs = CTabs TabsBase #

data GetPush a #

data SetPush a #

data Which a #

data ClientArea a #

data TabHeight a #

data GetTabAlign a #

data SetTabAlign a #

type SpinnerBase = CSpinnerBase GroupBase #

type Spinner = CSpinner SpinnerBase #

data GetFormat a #

data SetFormat a #

type ColorChooserBase = CColorChooserBase GroupBase #

type ColorChooser = CColorChooser ColorChooserBase #

data GetHue a #

data GetR a #

data GetG a #

data GetB a #

data SetHsv a #

data SetRgb a #

data GetRgb a #

data GetHsv a #

type FileBrowserBase = CFileBrowserBase BrowserBase #

type FileBrowser = CFileBrowser FileBrowserBase #

data SetIconsize a #

data GetIconsize a #

data SetFiletype a #

data GetFiletype a #

type RGBImage = CRGBImage Image #

type JPEGImage = CJPEGImage RGBImage #

type BMPImage = CBMPImage RGBImage #

type GIFImage = CGIFImage RGBImage #

type XBMImage = CXBMImage RGBImage #

type XPMImage = CXPMImage RGBImage #

type PNGImage = CPNGImage RGBImage #

type PNMImage = CPNMImage RGBImage #

type FileInputBase = CFileInputBase InputBase #

type FileInput = CFileInput FileInputBase #

type ScreenDriver = CScreenDriver Base #

type SystemDriver = CSystemDriver Base #

type SVGImage = CSVGImage RGBImage #

type SimpleTerminalBase = CSimpleTerminalBase TextDisplayBase #

type SimpleTerminal = CSimpleTerminal SimpleTerminalBase #

data SetAnsi a #

data GetAnsi a #

data RemoveLines a #

type MultiLabel = CMultiLabel Base #

data WidgetLabel a #

dispatch :: (Match obj ~ FindOp origObj origObj op, Op op obj origObj impl) => op -> Ref origObj -> impl #

Given some member function op and a Ref to some class origObj return the implementation of op. See Op for more details.

Every FLTK function called on some Ref uses this function to figure out what arguments it needs.

safeCast :: Parent a r => Ref a -> Ref r #

Cast any reference to one of its ancestors.

castTo :: Ref a -> Ref r #

Cast any reference to any other reference. Unsafe, intended to be used by Op.

data Match a #

See FindOp for more details.

data NoFunction a b #

See FindOp for more details.

type family FindOp orig hierarchy needle :: * where ... #

Equations

FindOp (w ws) () (n ()) = (TypeError (((ShowType n :<>: Text " is not supported by ") :<>: ShowType w) :<>: ShowType (Functions ws)) :: *) 
FindOp orig hierarchy needle = FindOpHelper orig hierarchy needle (Contains (Functions hierarchy) needle) 

class Parent a b #

A class with a single instance that is found only if b is an ancestor of a.

Used by some Op implementations to enforce that certain parameters have to be at least a b.

Instances
InHierarchy ~ FindInHierarchy a a b => Parent a b 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Dispatch

type family Functions x :: * #

Associate a "class" with it's member functions

Instances
type Functions WidgetBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Widget 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions GroupBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions GroupBase = GroupBaseFuncs
type Functions Group 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Group = GroupFuncs
type Functions WindowBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions WindowBase = WindowBaseFuncs
type Functions Window 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Window = WindowFuncs
type Functions SingleWindowBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions SingleWindowBase = SingleWindowBaseFuncs
type Functions SingleWindow 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions SingleWindow = SingleWindowFuncs
type Functions DoubleWindowBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions DoubleWindowBase = DoubleWindowBaseFuncs
type Functions DoubleWindow 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions DoubleWindow = DoubleWindowFuncs
type Functions OverlayWindowBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions OverlayWindowBase = OverlayWindowBaseFuncs
type Functions OverlayWindow 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions OverlayWindow = OverlayWindowFuncs
type Functions ButtonBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions ButtonBase = ButtonBaseFuncs
type Functions Button 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Button = ButtonFuncs
type Functions LightButtonBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions LightButtonBase = LightButtonBaseFuncs
type Functions LightButton 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions LightButton = LightButtonFuncs
type Functions RadioLightButtonBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions RadioLightButton 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions CheckButtonBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions CheckButtonBase = CheckButtonBaseFuncs
type Functions CheckButton 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions CheckButton = CheckButtonFuncs
type Functions ReturnButtonBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions ReturnButtonBase = ReturnButtonBaseFuncs
type Functions ReturnButton 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions ReturnButton = ReturnButtonFuncs
type Functions RoundButtonBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions RoundButtonBase = RoundButtonBaseFuncs
type Functions RoundButton 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions RoundButton = RoundButtonFuncs
type Functions RepeatButtonBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions RepeatButtonBase = RepeatButtonBaseFuncs
type Functions RepeatButton 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions RepeatButton = RepeatButtonFuncs
type Functions ToggleButtonBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions ToggleButtonBase = ToggleButtonBaseFuncs
type Functions ToggleButton 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions ToggleButton = ToggleButtonFuncs
type Functions ValuatorBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions ValuatorBase = ValuatorBaseFuncs
type Functions Valuator 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Valuator = ValuatorFuncs
type Functions SliderBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions SliderBase = SliderBaseFuncs
type Functions Slider 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Slider = SliderFuncs
type Functions FillSliderBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions FillSlider 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions HorSliderBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions HorSlider 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions HorFillSliderBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions HorFillSlider 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions NiceSliderBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions NiceSlider 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions HorNiceSliderBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions HorNiceSlider 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions MenuItemBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions MenuItemBase = MenuItemBaseFuncs
type Functions MenuItem 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions MenuItem = MenuItemFuncs
type Functions MenuPrimBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions MenuPrimBase = MenuPrimBaseFuncs
type Functions MenuPrim 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions MenuPrim = MenuPrimFuncs
type Functions MenuBarBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions MenuBarBase = MenuBarBaseFuncs
type Functions MenuBar 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions MenuBar = MenuBarFuncs
type Functions SysMenuBarBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions SysMenuBarBase = SysMenuBarBaseFuncs
type Functions SysMenuBar 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions SysMenuBar = SysMenuBarFuncs
type Functions ChoiceBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions ChoiceBase = ChoiceBaseFuncs
type Functions Choice 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Choice = ChoiceFuncs
type Functions MenuButtonBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions MenuButtonBase = MenuButtonBaseFuncs
type Functions MenuButton 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions MenuButton = MenuButtonFuncs
type Functions Image 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Image = ImageFuncs
type Functions Bitmap 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Bitmap = BitmapFuncs
type Functions Pixmap 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Pixmap = PixmapFuncs
type Functions CopySurface 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions CopySurface = CopySurfaceFuncs
type Functions ImageSurface 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions ImageSurface = ImageSurfaceFuncs
type Functions AdjusterBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions AdjusterBase = AdjusterBaseFuncs
type Functions Adjuster 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Adjuster = AdjusterFuncs
type Functions DialBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions DialBase = DialBaseFuncs
type Functions Dial 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Dial = DialFuncs
type Functions FillDial 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions LineDial 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions RollerBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions RollerBase = RollerBaseFuncs
type Functions Roller 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Roller = RollerFuncs
type Functions CounterBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions CounterBase = CounterBaseFuncs
type Functions Counter 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Counter = CounterFuncs
type Functions ScrollbarBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions ScrollbarBase = ScrollbarBaseFuncs
type Functions Scrollbar 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Scrollbar = ScrollbarFuncs
type Functions ValueSliderBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions ValueSliderBase = ValueSliderBaseFuncs
type Functions ValueSlider 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions ValueSlider = ValueSliderFuncs
type Functions HorValueSlider 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions InputBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions InputBase = InputBaseFuncs
type Functions Input 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Input = InputFuncs
type Functions OutputBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions OutputBase = OutputBaseFuncs
type Functions Output 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Output = OutputFuncs
type Functions ValueInputBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions ValueInputBase = ValueInputBaseFuncs
type Functions ValueInput 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions ValueInput = ValueInputFuncs
type Functions ValueOutputBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions ValueOutputBase = ValueOutputBaseFuncs
type Functions ValueOutput 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions ValueOutput = ValueOutputFuncs
type Functions ProgressBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions ProgressBase = ProgressBaseFuncs
type Functions Progress 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Progress = ProgressFuncs
type Functions PositionerBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions PositionerBase = PositionerBaseFuncs
type Functions Positioner 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Positioner = PositionerFuncs
type Functions WizardBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions WizardBase = WizardBaseFuncs
type Functions Wizard 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Wizard = WizardFuncs
type Functions TableBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions TableBase = TableBaseFuncs
type Functions Table 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Table = TableFuncs
type Functions TableRowBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions TableRowBase = TableRowBaseFuncs
type Functions TableRow 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions TableRow = TableRowFuncs
type Functions GlWindowBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions GlWindowBase = GlWindowBaseFuncs
type Functions GlWindow 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions GlWindow = GlWindowFuncs
type Functions Box 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Box = ()
type Functions BrowserBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions BrowserBase = BrowserBaseFuncs
type Functions Browser 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Browser = BrowserFuncs
type Functions SelectBrowser 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions IntInput 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions ClockBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions ClockBase = ClockBaseFuncs
type Functions Clock 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Clock = ClockFuncs
type Functions TreePrefs 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions TreePrefs = TreePrefsFuncs
type Functions TreeItem 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions TreeItem = TreeItemFuncs
type Functions TreeBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions TreeBase = TreeBaseFuncs
type Functions Tree 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Tree = TreeFuncs
type Functions TextSelection 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions TextSelection = TextSelectionFuncs
type Functions TextBuffer 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions TextBuffer = TextBufferFuncs
type Functions TextDisplayBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions TextDisplayBase = TextDisplayBaseFuncs
type Functions TextDisplay 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions TextDisplay = TextDisplayFuncs
type Functions TextEditorBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions TextEditorBase = TextEditorBaseFuncs
type Functions TextEditor 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions TextEditor = TextEditorFuncs
type Functions NativeFileChooser 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions NativeFileChooser = NativeFileChooserFuncs
type Functions TileBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions TileBase = TileBaseFuncs
type Functions Tile 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Tile = TileFuncs
type Functions PackBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions PackBase = PackBaseFuncs
type Functions Pack 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Pack = PackFuncs
type Functions ScrolledBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions ScrolledBase = ScrolledBaseFuncs
type Functions Scrolled 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Scrolled = ScrolledFuncs
type Functions TabsBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions TabsBase = TabsBaseFuncs
type Functions Tabs 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Tabs = TabsFuncs
type Functions SpinnerBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions SpinnerBase = SpinnerBaseFuncs
type Functions Spinner 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Spinner = SpinnerFuncs
type Functions ColorChooserBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions ColorChooserBase = ColorChooserBaseFuncs
type Functions ColorChooser 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions ColorChooser = ColorChooserFuncs
type Functions FileBrowserBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions FileBrowserBase = FileBrowserBaseFuncs
type Functions FileBrowser 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions FileBrowser = FileBrowserFuncs
type Functions RGBImage 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions RGBImage = RGBImageFuncs
type Functions JPEGImage 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions BMPImage 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions GIFImage 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions XBMImage 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions XPMImage 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions PNGImage 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions PNMImage 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions FileInputBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions FileInputBase = FileInputBaseFuncs
type Functions FileInput 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions FileInput = FileInputFuncs
type Functions ScreenDriver 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions SystemDriver 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions SVGImage 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions SVGImage = SVGImageFuncs
type Functions SimpleTerminalBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions SimpleTerminalBase = SimpleTerminalBaseFuncs
type Functions SimpleTerminal 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions SimpleTerminal = SimpleTerminalFuncs
type Functions MultiLabel 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions MultiLabel = MultiLabelFuncs
type Functions Base 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Base = ()

class Op op obj origObj impl where #

Implementations of methods on various types of objects.

  • op - name of the function
  • obj - the class that implements op
  • origObj - the class in the hierarchy where the search for op started.

whose implementation is usually found much lower in the hierarchy but where we also want to enforce that the implementation take the type of the widget calling it. * impl - a function that takes the a Ref origobj, casted down to Ref obj and whatever other parameters the instance specifies.

Minimal complete definition

runOp

Methods

runOp :: op -> origObj -> Ref obj -> impl #

refPtrEquals :: Ref a -> Ref b -> IO Bool #

swapRef :: Ref a -> (Ptr b -> IO (Ptr ())) -> IO () #

withMaybeRef :: Maybe (Ref a) -> (Ptr () -> IO c) -> IO c #

withRefs :: HasCallStack => [Ref a] -> (Ptr (Ptr b) -> IO c) -> IO c #

isNull :: Ref a -> IO Bool #

withRef :: HasCallStack => Ref a -> (Ptr b -> IO c) -> IO c #

toRefPtr :: HasCallStack => Ptr (Ptr a) -> IO (Ptr a) #

withForeignPtrs :: [ForeignPtr a] -> ([Ptr a] -> IO c) -> IO c #

toSize :: (Int, Int) -> Size #

successOrOutOfRange :: a -> Bool -> (a -> IO b) -> IO (Either OutOfRange b) #

data FileBrowserType #

data FileChooserType #

data TreeReasonType #

data ColorChooserMode #

Constructors

RgbMode 
ByteMode 
HexMode 
HsvMode 

data TableRowSelectMode #

Instances
Enum TableRowSelectMode 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Eq TableRowSelectMode 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Ord TableRowSelectMode 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Show TableRowSelectMode 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

data ScrollbarMode #

type FlColor = CUInt #

type FlFont = CInt #

type FlAlign = CUInt #

type Delta = Maybe Int #

type ID = Ptr () #

type Fl_Region = Ptr () #

newtype WindowHandle #

Constructors

WindowHandle (Ptr ()) 

data Ref a #

Constructors

Ref !(ForeignPtr (Ptr ())) 
Instances
Eq (Ref a) 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Methods

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

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

Ord (Ref a) 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Methods

compare :: Ref a -> Ref a -> Ordering #

(<) :: Ref a -> Ref a -> Bool #

(<=) :: Ref a -> Ref a -> Bool #

(>) :: Ref a -> Ref a -> Bool #

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

max :: Ref a -> Ref a -> Ref a #

min :: Ref a -> Ref a -> Ref a #

Show (Ref a) 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Methods

showsPrec :: Int -> Ref a -> ShowS #

show :: Ref a -> String #

showList :: [Ref a] -> ShowS #

data FunRef #

Constructors

FunRef !(FunPtr ()) 

data CBase parent #

Instances
type Functions WidgetBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Widget 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions GroupBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions GroupBase = GroupBaseFuncs
type Functions Group 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Group = GroupFuncs
type Functions WindowBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions WindowBase = WindowBaseFuncs
type Functions Window 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Window = WindowFuncs
type Functions SingleWindowBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions SingleWindowBase = SingleWindowBaseFuncs
type Functions SingleWindow 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions SingleWindow = SingleWindowFuncs
type Functions DoubleWindowBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions DoubleWindowBase = DoubleWindowBaseFuncs
type Functions DoubleWindow 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions DoubleWindow = DoubleWindowFuncs
type Functions OverlayWindowBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions OverlayWindowBase = OverlayWindowBaseFuncs
type Functions OverlayWindow 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions OverlayWindow = OverlayWindowFuncs
type Functions ButtonBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions ButtonBase = ButtonBaseFuncs
type Functions Button 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Button = ButtonFuncs
type Functions LightButtonBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions LightButtonBase = LightButtonBaseFuncs
type Functions LightButton 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions LightButton = LightButtonFuncs
type Functions RadioLightButtonBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions RadioLightButton 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions CheckButtonBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions CheckButtonBase = CheckButtonBaseFuncs
type Functions CheckButton 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions CheckButton = CheckButtonFuncs
type Functions ReturnButtonBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions ReturnButtonBase = ReturnButtonBaseFuncs
type Functions ReturnButton 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions ReturnButton = ReturnButtonFuncs
type Functions RoundButtonBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions RoundButtonBase = RoundButtonBaseFuncs
type Functions RoundButton 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions RoundButton = RoundButtonFuncs
type Functions RepeatButtonBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions RepeatButtonBase = RepeatButtonBaseFuncs
type Functions RepeatButton 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions RepeatButton = RepeatButtonFuncs
type Functions ToggleButtonBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions ToggleButtonBase = ToggleButtonBaseFuncs
type Functions ToggleButton 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions ToggleButton = ToggleButtonFuncs
type Functions ValuatorBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions ValuatorBase = ValuatorBaseFuncs
type Functions Valuator 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Valuator = ValuatorFuncs
type Functions SliderBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions SliderBase = SliderBaseFuncs
type Functions Slider 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Slider = SliderFuncs
type Functions FillSliderBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions FillSlider 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions HorSliderBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions HorSlider 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions HorFillSliderBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions HorFillSlider 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions NiceSliderBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions NiceSlider 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions HorNiceSliderBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions HorNiceSlider 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions MenuItemBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions MenuItemBase = MenuItemBaseFuncs
type Functions MenuItem 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions MenuItem = MenuItemFuncs
type Functions MenuPrimBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions MenuPrimBase = MenuPrimBaseFuncs
type Functions MenuPrim 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions MenuPrim = MenuPrimFuncs
type Functions MenuBarBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions MenuBarBase = MenuBarBaseFuncs
type Functions MenuBar 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions MenuBar = MenuBarFuncs
type Functions SysMenuBarBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions SysMenuBarBase = SysMenuBarBaseFuncs
type Functions SysMenuBar 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions SysMenuBar = SysMenuBarFuncs
type Functions ChoiceBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions ChoiceBase = ChoiceBaseFuncs
type Functions Choice 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Choice = ChoiceFuncs
type Functions MenuButtonBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions MenuButtonBase = MenuButtonBaseFuncs
type Functions MenuButton 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions MenuButton = MenuButtonFuncs
type Functions Image 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Image = ImageFuncs
type Functions Bitmap 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Bitmap = BitmapFuncs
type Functions Pixmap 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Pixmap = PixmapFuncs
type Functions CopySurface 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions CopySurface = CopySurfaceFuncs
type Functions ImageSurface 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions ImageSurface = ImageSurfaceFuncs
type Functions AdjusterBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions AdjusterBase = AdjusterBaseFuncs
type Functions Adjuster 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Adjuster = AdjusterFuncs
type Functions DialBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions DialBase = DialBaseFuncs
type Functions Dial 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Dial = DialFuncs
type Functions FillDial 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions LineDial 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions RollerBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions RollerBase = RollerBaseFuncs
type Functions Roller 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Roller = RollerFuncs
type Functions CounterBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions CounterBase = CounterBaseFuncs
type Functions Counter 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Counter = CounterFuncs
type Functions ScrollbarBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions ScrollbarBase = ScrollbarBaseFuncs
type Functions Scrollbar 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Scrollbar = ScrollbarFuncs
type Functions ValueSliderBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions ValueSliderBase = ValueSliderBaseFuncs
type Functions ValueSlider 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions ValueSlider = ValueSliderFuncs
type Functions HorValueSlider 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions InputBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions InputBase = InputBaseFuncs
type Functions Input 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Input = InputFuncs
type Functions OutputBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions OutputBase = OutputBaseFuncs
type Functions Output 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Output = OutputFuncs
type Functions ValueInputBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions ValueInputBase = ValueInputBaseFuncs
type Functions ValueInput 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions ValueInput = ValueInputFuncs
type Functions ValueOutputBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions ValueOutputBase = ValueOutputBaseFuncs
type Functions ValueOutput 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions ValueOutput = ValueOutputFuncs
type Functions ProgressBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions ProgressBase = ProgressBaseFuncs
type Functions Progress 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Progress = ProgressFuncs
type Functions PositionerBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions PositionerBase = PositionerBaseFuncs
type Functions Positioner 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Positioner = PositionerFuncs
type Functions WizardBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions WizardBase = WizardBaseFuncs
type Functions Wizard 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Wizard = WizardFuncs
type Functions TableBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions TableBase = TableBaseFuncs
type Functions Table 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Table = TableFuncs
type Functions TableRowBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions TableRowBase = TableRowBaseFuncs
type Functions TableRow 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions TableRow = TableRowFuncs
type Functions GlWindowBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions GlWindowBase = GlWindowBaseFuncs
type Functions GlWindow 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions GlWindow = GlWindowFuncs
type Functions Box 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Box = ()
type Functions BrowserBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions BrowserBase = BrowserBaseFuncs
type Functions Browser 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Browser = BrowserFuncs
type Functions SelectBrowser 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions IntInput 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions ClockBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions ClockBase = ClockBaseFuncs
type Functions Clock 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Clock = ClockFuncs
type Functions TreePrefs 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions TreePrefs = TreePrefsFuncs
type Functions TreeItem 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions TreeItem = TreeItemFuncs
type Functions TreeBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions TreeBase = TreeBaseFuncs
type Functions Tree 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Tree = TreeFuncs
type Functions TextSelection 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions TextSelection = TextSelectionFuncs
type Functions TextBuffer 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions TextBuffer = TextBufferFuncs
type Functions TextDisplayBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions TextDisplayBase = TextDisplayBaseFuncs
type Functions TextDisplay 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions TextDisplay = TextDisplayFuncs
type Functions TextEditorBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions TextEditorBase = TextEditorBaseFuncs
type Functions TextEditor 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions TextEditor = TextEditorFuncs
type Functions NativeFileChooser 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions NativeFileChooser = NativeFileChooserFuncs
type Functions TileBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions TileBase = TileBaseFuncs
type Functions Tile 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Tile = TileFuncs
type Functions PackBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions PackBase = PackBaseFuncs
type Functions Pack 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Pack = PackFuncs
type Functions ScrolledBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions ScrolledBase = ScrolledBaseFuncs
type Functions Scrolled 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Scrolled = ScrolledFuncs
type Functions TabsBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions TabsBase = TabsBaseFuncs
type Functions Tabs 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Tabs = TabsFuncs
type Functions SpinnerBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions SpinnerBase = SpinnerBaseFuncs
type Functions Spinner 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Spinner = SpinnerFuncs
type Functions ColorChooserBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions ColorChooserBase = ColorChooserBaseFuncs
type Functions ColorChooser 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions ColorChooser = ColorChooserFuncs
type Functions FileBrowserBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions FileBrowserBase = FileBrowserBaseFuncs
type Functions FileBrowser 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions FileBrowser = FileBrowserFuncs
type Functions RGBImage 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions RGBImage = RGBImageFuncs
type Functions JPEGImage 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions BMPImage 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions GIFImage 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions XBMImage 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions XPMImage 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions PNGImage 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions PNMImage 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions FileInputBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions FileInputBase = FileInputBaseFuncs
type Functions FileInput 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions FileInput = FileInputFuncs
type Functions ScreenDriver 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions SystemDriver 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions SVGImage 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions SVGImage = SVGImageFuncs
type Functions SimpleTerminalBase 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions SimpleTerminalBase = SimpleTerminalBaseFuncs
type Functions SimpleTerminal 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions SimpleTerminal = SimpleTerminalFuncs
type Functions MultiLabel 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions MultiLabel = MultiLabelFuncs
type Functions Base 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Base = ()

type Base = CBase () #

type GlobalCallback = IO () #

type CallbackWithUserDataPrim = Ptr () -> Ptr () -> IO () #

type CallbackPrim = Ptr () -> IO () #

type CustomColorAveragePrim = Ptr () -> CUInt -> CFloat -> IO () #

type CustomImageDrawPrim = Ptr () -> CInt -> CInt -> CInt -> CInt -> CInt -> CInt -> IO () #

type CustomImageCopyPrim = Ptr () -> CInt -> CInt -> IO (Ptr ()) #

type DrawCallback = Text -> Position -> IO () #

type DrawCallbackPrim = CString -> CInt -> CInt -> CInt -> IO () #

type TextBufferCallback = FunPtr (Ptr () -> IO ()) #

type FileChooserCallback = FunPtr (Ptr () -> Ptr () -> IO ()) #

type BoxDrawF = Rectangle -> Color -> IO () #

type BoxDrawFPrim = CInt -> CInt -> CInt -> CInt -> FlColor -> IO () #

type FDHandlerPrim = Fl_Socket -> Ptr () -> IO () #

type FDHandler = FlSocket -> IO () #

type TextModifyCbPrim = CInt -> CInt -> CInt -> CInt -> Ptr CChar -> Ptr () -> IO () #

type TextPredeleteCbPrim = CInt -> CInt -> Ptr () -> IO () #

type UnfinishedStyleCbPrim = CInt -> Ptr () -> IO () #

type MenuItemDrawF = Ptr () -> CInt -> CInt -> CInt -> CInt -> Ptr () -> CInt -> IO () #

type TabPositionsPrim = Ptr () -> Ptr CInt -> Ptr CInt -> IO CInt #

type TabHeightPrim = Ptr () -> IO CInt #

type TabWhichPrim = Ptr () -> CInt -> CInt -> IO (Ptr ()) #

type TabClientAreaPrim = Ptr () -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> CInt -> IO () #

type GetIntPrim = Ptr () -> IO CInt #

type SetIntPrim = Ptr () -> CInt -> IO () #

type ColorSetPrim = Ptr () -> CDouble -> CDouble -> CDouble -> IO CInt #

type DestroyCallbacksPrim = Ptr () -> Ptr () -> IO () #

newtype Width #

Constructors

Width Int 
Instances
Eq Width 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Methods

(==) :: Width -> Width -> Bool #

(/=) :: Width -> Width -> Bool #

Ord Width 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Methods

compare :: Width -> Width -> Ordering #

(<) :: Width -> Width -> Bool #

(<=) :: Width -> Width -> Bool #

(>) :: Width -> Width -> Bool #

(>=) :: Width -> Width -> Bool #

max :: Width -> Width -> Width #

min :: Width -> Width -> Width #

Show Width 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Methods

showsPrec :: Int -> Width -> ShowS #

show :: Width -> String #

showList :: [Width] -> ShowS #

newtype Height #

Constructors

Height Int 
Instances
Eq Height 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Methods

(==) :: Height -> Height -> Bool #

(/=) :: Height -> Height -> Bool #

Ord Height 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Show Height 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

newtype Depth #

Constructors

Depth Int 
Instances
Eq Depth 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Methods

(==) :: Depth -> Depth -> Bool #

(/=) :: Depth -> Depth -> Bool #

Ord Depth 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Methods

compare :: Depth -> Depth -> Ordering #

(<) :: Depth -> Depth -> Bool #

(<=) :: Depth -> Depth -> Bool #

(>) :: Depth -> Depth -> Bool #

(>=) :: Depth -> Depth -> Bool #

max :: Depth -> Depth -> Depth #

min :: Depth -> Depth -> Depth #

Show Depth 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Methods

showsPrec :: Int -> Depth -> ShowS #

show :: Depth -> String #

showList :: [Depth] -> ShowS #

newtype X #

Constructors

X Int 
Instances
Eq X 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Methods

(==) :: X -> X -> Bool #

(/=) :: X -> X -> Bool #

Ord X 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Methods

compare :: X -> X -> Ordering #

(<) :: X -> X -> Bool #

(<=) :: X -> X -> Bool #

(>) :: X -> X -> Bool #

(>=) :: X -> X -> Bool #

max :: X -> X -> X #

min :: X -> X -> X #

Show X 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Methods

showsPrec :: Int -> X -> ShowS #

show :: X -> String #

showList :: [X] -> ShowS #

newtype Y #

Constructors

Y Int 
Instances
Eq Y 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Methods

(==) :: Y -> Y -> Bool #

(/=) :: Y -> Y -> Bool #

Ord Y 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Methods

compare :: Y -> Y -> Ordering #

(<) :: Y -> Y -> Bool #

(<=) :: Y -> Y -> Bool #

(>) :: Y -> Y -> Bool #

(>=) :: Y -> Y -> Bool #

max :: Y -> Y -> Y #

min :: Y -> Y -> Y #

Show Y 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Methods

showsPrec :: Int -> Y -> ShowS #

show :: Y -> String #

showList :: [Y] -> ShowS #

newtype ByX #

Constructors

ByX Double 
Instances
Eq ByX 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Methods

(==) :: ByX -> ByX -> Bool #

(/=) :: ByX -> ByX -> Bool #

Ord ByX 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Methods

compare :: ByX -> ByX -> Ordering #

(<) :: ByX -> ByX -> Bool #

(<=) :: ByX -> ByX -> Bool #

(>) :: ByX -> ByX -> Bool #

(>=) :: ByX -> ByX -> Bool #

max :: ByX -> ByX -> ByX #

min :: ByX -> ByX -> ByX #

Show ByX 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Methods

showsPrec :: Int -> ByX -> ShowS #

show :: ByX -> String #

showList :: [ByX] -> ShowS #

newtype ByY #

Constructors

ByY Double 
Instances
Eq ByY 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Methods

(==) :: ByY -> ByY -> Bool #

(/=) :: ByY -> ByY -> Bool #

Ord ByY 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Methods

compare :: ByY -> ByY -> Ordering #

(<) :: ByY -> ByY -> Bool #

(<=) :: ByY -> ByY -> Bool #

(>) :: ByY -> ByY -> Bool #

(>=) :: ByY -> ByY -> Bool #

max :: ByY -> ByY -> ByY #

min :: ByY -> ByY -> ByY #

Show ByY 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Methods

showsPrec :: Int -> ByY -> ShowS #

show :: ByY -> String #

showList :: [ByY] -> ShowS #

newtype Angle #

Constructors

Angle CShort 
Instances
Eq Angle 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Methods

(==) :: Angle -> Angle -> Bool #

(/=) :: Angle -> Angle -> Bool #

Ord Angle 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Methods

compare :: Angle -> Angle -> Ordering #

(<) :: Angle -> Angle -> Bool #

(<=) :: Angle -> Angle -> Bool #

(>) :: Angle -> Angle -> Bool #

(>=) :: Angle -> Angle -> Bool #

max :: Angle -> Angle -> Angle #

min :: Angle -> Angle -> Angle #

Show Angle 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Methods

showsPrec :: Int -> Angle -> ShowS #

show :: Angle -> String #

showList :: [Angle] -> ShowS #

data DPI #

Constructors

DPI Float Float 
Instances
Eq DPI 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Methods

(==) :: DPI -> DPI -> Bool #

(/=) :: DPI -> DPI -> Bool #

Ord DPI 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Methods

compare :: DPI -> DPI -> Ordering #

(<) :: DPI -> DPI -> Bool #

(<=) :: DPI -> DPI -> Bool #

(>) :: DPI -> DPI -> Bool #

(>=) :: DPI -> DPI -> Bool #

max :: DPI -> DPI -> DPI #

min :: DPI -> DPI -> DPI #

Show DPI 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Methods

showsPrec :: Int -> DPI -> ShowS #

show :: DPI -> String #

showList :: [DPI] -> ShowS #

data ByXY #

Constructors

ByXY ByX ByY 
Instances
Eq ByXY 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Methods

(==) :: ByXY -> ByXY -> Bool #

(/=) :: ByXY -> ByXY -> Bool #

Ord ByXY 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Methods

compare :: ByXY -> ByXY -> Ordering #

(<) :: ByXY -> ByXY -> Bool #

(<=) :: ByXY -> ByXY -> Bool #

(>) :: ByXY -> ByXY -> Bool #

(>=) :: ByXY -> ByXY -> Bool #

max :: ByXY -> ByXY -> ByXY #

min :: ByXY -> ByXY -> ByXY #

Show ByXY 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Methods

showsPrec :: Int -> ByXY -> ShowS #

show :: ByXY -> String #

showList :: [ByXY] -> ShowS #

data Size #

Constructors

Size Width Height 
Instances
Eq Size 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Methods

(==) :: Size -> Size -> Bool #

(/=) :: Size -> Size -> Bool #

Ord Size 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Methods

compare :: Size -> Size -> Ordering #

(<) :: Size -> Size -> Bool #

(<=) :: Size -> Size -> Bool #

(>) :: Size -> Size -> Bool #

(>=) :: Size -> Size -> Bool #

max :: Size -> Size -> Size #

min :: Size -> Size -> Size #

Show Size 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Methods

showsPrec :: Int -> Size -> ShowS #

show :: Size -> String #

showList :: [Size] -> ShowS #

newtype Lines #

Constructors

Lines Int 
Instances
Eq Lines 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Methods

(==) :: Lines -> Lines -> Bool #

(/=) :: Lines -> Lines -> Bool #

Ord Lines 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Methods

compare :: Lines -> Lines -> Ordering #

(<) :: Lines -> Lines -> Bool #

(<=) :: Lines -> Lines -> Bool #

(>) :: Lines -> Lines -> Bool #

(>=) :: Lines -> Lines -> Bool #

max :: Lines -> Lines -> Lines #

min :: Lines -> Lines -> Lines #

Show Lines 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Methods

showsPrec :: Int -> Lines -> ShowS #

show :: Lines -> String #

showList :: [Lines] -> ShowS #

newtype AtIndex #

Constructors

AtIndex Int 
Instances
Eq AtIndex 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Methods

(==) :: AtIndex -> AtIndex -> Bool #

(/=) :: AtIndex -> AtIndex -> Bool #

Ord AtIndex 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Show AtIndex 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

newtype Rows #

Constructors

Rows Int 
Instances
Eq Rows 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Methods

(==) :: Rows -> Rows -> Bool #

(/=) :: Rows -> Rows -> Bool #

Ord Rows 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Methods

compare :: Rows -> Rows -> Ordering #

(<) :: Rows -> Rows -> Bool #

(<=) :: Rows -> Rows -> Bool #

(>) :: Rows -> Rows -> Bool #

(>=) :: Rows -> Rows -> Bool #

max :: Rows -> Rows -> Rows #

min :: Rows -> Rows -> Rows #

Show Rows 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Methods

showsPrec :: Int -> Rows -> ShowS #

show :: Rows -> String #

showList :: [Rows] -> ShowS #

newtype Columns #

Constructors

Columns Int 
Instances
Eq Columns 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Methods

(==) :: Columns -> Columns -> Bool #

(/=) :: Columns -> Columns -> Bool #

Ord Columns 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Show Columns 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

newtype FlOffscreen #

The type of Fl_Offscreen varies wildly from platform to platform. Feel free to examine the insides when debugging but any computation based on it will probably not be portable.

newtype FlBitmask #

Constructors

FlBitmask Fl_Bitmask 

newtype FlRegion #

Constructors

FlRegion Fl_Region 

newtype FlSocket #

Constructors

FlSocket Fl_Socket 

type Fl_GlContext = Ptr () #

newtype FlGlContext #

newtype GapSize #

Constructors

GapSize Int 
Instances
Eq GapSize 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Methods

(==) :: GapSize -> GapSize -> Bool #

(/=) :: GapSize -> GapSize -> Bool #

Ord GapSize 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Show GapSize 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types