fltkhs-0.7.0.4: FLTK bindings

Safe HaskellNone
LanguageHaskell2010

Graphics.UI.FLTK.LowLevel.Fl_Types

Contents

Synopsis

Documentation

data FileBrowserType Source #

data FileIconProps Source #

data FileChooserType Source #

data TreeReasonType Source #

data MenuItemFlag Source #

data ColorChooserMode Source #

Constructors

RgbMode 
ByteMode 
HexMode 
HsvMode 
Instances
Enum ColorChooserMode Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Eq ColorChooserMode Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Ord ColorChooserMode Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Show ColorChooserMode Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

data TableRowSelectMode Source #

Instances
Enum TableRowSelectMode Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Eq TableRowSelectMode Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Ord TableRowSelectMode Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Show TableRowSelectMode Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

data ScrollbarMode Source #

type ID = Ptr () Source #

type Fl_Region = Ptr () Source #

newtype WindowHandle Source #

Constructors

WindowHandle (Ptr ()) 

data Ref a Source #

Constructors

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

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Methods

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

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

Ord (Ref a) Source # 
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) Source # 
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 Source #

Constructors

FunRef !(FunPtr ()) 

The FLTK widget hierarchy

data CBase parent Source #

Instances
(Parent a MenuItem, impl ~ (Ref a -> IO ())) => Op (MenuItemLabel ()) MultiLabel orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MultiLabel

Methods

runOp :: MenuItemLabel () -> orig -> Ref MultiLabel -> impl Source #

(Parent a Widget, impl ~ (Ref a -> IO ())) => Op (WidgetLabel ()) MultiLabel orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MultiLabel

Methods

runOp :: WidgetLabel () -> orig -> Ref MultiLabel -> impl Source #

impl ~ (LineNumber -> LineNumber -> IO ()) => Op (RemoveLines ()) SimpleTerminal orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.SimpleTerminal

Methods

runOp :: RemoveLines () -> orig -> Ref SimpleTerminal -> impl Source #

impl ~ IO AtIndex => Op (GetCurrentStyleIndex ()) SimpleTerminal orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.SimpleTerminal

Methods

runOp :: GetCurrentStyleIndex () -> orig -> Ref SimpleTerminal -> impl Source #

impl ~ (AtIndex -> IO ()) => Op (SetCurrentStyleIndex ()) SimpleTerminal orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.SimpleTerminal

Methods

runOp :: SetCurrentStyleIndex () -> orig -> Ref SimpleTerminal -> impl Source #

impl ~ IO AtIndex => Op (GetNormalStyleIndex ()) SimpleTerminal orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.SimpleTerminal

Methods

runOp :: GetNormalStyleIndex () -> orig -> Ref SimpleTerminal -> impl Source #

impl ~ (AtIndex -> IO ()) => Op (SetNormalStyleIndex ()) SimpleTerminal orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.SimpleTerminal

Methods

runOp :: SetNormalStyleIndex () -> orig -> Ref SimpleTerminal -> impl Source #

impl ~ IO Int => Op (GetStyleTableSize ()) SimpleTerminal orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.SimpleTerminal

Methods

runOp :: GetStyleTableSize () -> orig -> Ref SimpleTerminal -> impl Source #

impl ~ IO (Maybe [StyleTableEntry]) => Op (GetStyleTable ()) SimpleTerminal orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.SimpleTerminal

Methods

runOp :: GetStyleTable () -> orig -> Ref SimpleTerminal -> impl Source #

impl ~ ([StyleTableEntry] -> Maybe Int -> IO ()) => Op (SetStyleTable ()) SimpleTerminal orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.SimpleTerminal

Methods

runOp :: SetStyleTable () -> orig -> Ref SimpleTerminal -> impl Source #

impl ~ IO Bool => Op (GetAnsi ()) SimpleTerminal orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.SimpleTerminal

Methods

runOp :: GetAnsi () -> orig -> Ref SimpleTerminal -> impl Source #

impl ~ (Bool -> IO ()) => Op (SetAnsi ()) SimpleTerminal orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.SimpleTerminal

Methods

runOp :: SetAnsi () -> orig -> Ref SimpleTerminal -> impl Source #

impl ~ IO Lines => Op (GetHistoryLines ()) SimpleTerminal orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.SimpleTerminal

Methods

runOp :: GetHistoryLines () -> orig -> Ref SimpleTerminal -> impl Source #

impl ~ (Lines -> IO ()) => Op (SetHistoryLines ()) SimpleTerminal orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.SimpleTerminal

Methods

runOp :: SetHistoryLines () -> orig -> Ref SimpleTerminal -> impl Source #

impl ~ IO Bool => Op (GetStayAtBottom ()) SimpleTerminal orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.SimpleTerminal

Methods

runOp :: GetStayAtBottom () -> orig -> Ref SimpleTerminal -> impl Source #

impl ~ (Bool -> IO ()) => Op (SetStayAtBottom ()) SimpleTerminal orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.SimpleTerminal

Methods

runOp :: SetStayAtBottom () -> orig -> Ref SimpleTerminal -> impl Source #

impl ~ IO Color => Op (GetErrorColor ()) FileInput orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.FileInput

Methods

runOp :: GetErrorColor () -> orig -> Ref FileInput -> impl Source #

impl ~ (Color -> IO ()) => Op (SetErrorColor ()) FileInput orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.FileInput

Methods

runOp :: SetErrorColor () -> orig -> Ref FileInput -> impl Source #

impl ~ IO FileBrowserType => Op (GetFiletype ()) FileBrowser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.FileBrowser

Methods

runOp :: GetFiletype () -> orig -> Ref FileBrowser -> impl Source #

impl ~ (FileBrowserType -> IO ()) => Op (SetFiletype ()) FileBrowser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.FileBrowser

Methods

runOp :: SetFiletype () -> orig -> Ref FileBrowser -> impl Source #

impl ~ IO CUChar => Op (GetIconsize ()) FileBrowser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.FileBrowser

Methods

runOp :: GetIconsize () -> orig -> Ref FileBrowser -> impl Source #

impl ~ (CUChar -> IO ()) => Op (SetIconsize ()) FileBrowser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.FileBrowser

Methods

runOp :: SetIconsize () -> orig -> Ref FileBrowser -> impl Source #

impl ~ IO (Either OutOfRange (Between0And6, Between0And1, Between0And1)) => Op (GetHsv ()) ColorChooser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ColorChooser

Methods

runOp :: GetHsv () -> orig -> Ref ColorChooser -> impl Source #

impl ~ IO (Either OutOfRange (Between0And1, Between0And1, Between0And1)) => Op (GetRgb ()) ColorChooser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ColorChooser

Methods

runOp :: GetRgb () -> orig -> Ref ColorChooser -> impl Source #

impl ~ ((Between0And1, Between0And1, Between0And1) -> IO (Either NoChange ())) => Op (SetRgb ()) ColorChooser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ColorChooser

Methods

runOp :: SetRgb () -> orig -> Ref ColorChooser -> impl Source #

impl ~ ((Between0And6, Between0And1, Between0And1) -> IO (Either NoChange ())) => Op (SetHsv ()) ColorChooser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ColorChooser

Methods

runOp :: SetHsv () -> orig -> Ref ColorChooser -> impl Source #

impl ~ IO (Either OutOfRange Between0And1) => Op (GetB ()) ColorChooser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ColorChooser

Methods

runOp :: GetB () -> orig -> Ref ColorChooser -> impl Source #

impl ~ IO (Either OutOfRange Between0And1) => Op (GetG ()) ColorChooser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ColorChooser

Methods

runOp :: GetG () -> orig -> Ref ColorChooser -> impl Source #

impl ~ IO (Either OutOfRange Between0And1) => Op (GetR ()) ColorChooser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ColorChooser

Methods

runOp :: GetR () -> orig -> Ref ColorChooser -> impl Source #

impl ~ IO (Either OutOfRange Between0And1) => Op (GetSaturation ()) ColorChooser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ColorChooser

Methods

runOp :: GetSaturation () -> orig -> Ref ColorChooser -> impl Source #

impl ~ IO (Either OutOfRange Between0And6) => Op (GetHue ()) ColorChooser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ColorChooser

Methods

runOp :: GetHue () -> orig -> Ref ColorChooser -> impl Source #

impl ~ (Text -> IO ()) => Op (SetFormat ()) Spinner orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Spinner

Methods

runOp :: SetFormat () -> orig -> Ref Spinner -> impl Source #

impl ~ IO (Maybe Text) => Op (GetFormat ()) Spinner orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Spinner

Methods

runOp :: GetFormat () -> orig -> Ref Spinner -> impl Source #

impl ~ (AlignType -> IO ()) => Op (SetTabAlign ()) Tabs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tabs

Methods

runOp :: SetTabAlign () -> orig -> Ref Tabs -> impl Source #

impl ~ IO AlignType => Op (GetTabAlign ()) Tabs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tabs

Methods

runOp :: GetTabAlign () -> orig -> Ref Tabs -> impl Source #

impl ~ IO Height => Op (TabHeight ()) Tabs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tabs

Methods

runOp :: TabHeight () -> orig -> Ref Tabs -> impl Source #

impl ~ IO AtIndex => Op (TabPositions ()) Tabs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tabs

Methods

runOp :: TabPositions () -> orig -> Ref Tabs -> impl Source #

impl ~ (TabsHeightOffset -> IO Rectangle) => Op (ClientArea ()) Tabs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tabs

Methods

runOp :: ClientArea () -> orig -> Ref Tabs -> impl Source #

impl ~ (Position -> IO (Maybe (Ref Widget))) => Op (Which ()) Tabs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tabs

Methods

runOp :: Which () -> orig -> Ref Tabs -> impl Source #

(Parent a Widget, impl ~ (Maybe (Ref a) -> IO (Either NoChange ()))) => Op (SetPush ()) Tabs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tabs

Methods

runOp :: SetPush () -> orig -> Ref Tabs -> impl Source #

impl ~ IO (Maybe (Ref Widget)) => Op (GetPush ()) Tabs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tabs

Methods

runOp :: GetPush () -> orig -> Ref Tabs -> impl Source #

impl ~ IO Int => Op (Yposition ()) Scrolled orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Scrolled

Methods

runOp :: Yposition () -> orig -> Ref Scrolled -> impl Source #

impl ~ IO Int => Op (Xposition ()) Scrolled orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Scrolled

Methods

runOp :: Xposition () -> orig -> Ref Scrolled -> impl Source #

impl ~ (Position -> IO ()) => Op (ScrollTo ()) Scrolled orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Scrolled

Methods

runOp :: ScrollTo () -> orig -> Ref Scrolled -> impl Source #

impl ~ IO Bool => Op (IsHorizontal ()) Pack orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Pack

Methods

runOp :: IsHorizontal () -> orig -> Ref Pack -> impl Source #

impl ~ IO Int => Op (GetSpacing ()) Pack orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Pack

Methods

runOp :: GetSpacing () -> orig -> Ref Pack -> impl Source #

impl ~ (Int -> IO ()) => Op (SetSpacing ()) Pack orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Pack

Methods

runOp :: SetSpacing () -> orig -> Ref Pack -> impl Source #

impl ~ IO (Maybe Text) => Op (GetErrmsg ()) NativeFileChooser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.NativeFileChooser

Methods

runOp :: GetErrmsg () -> orig -> Ref NativeFileChooser -> impl Source #

impl ~ IO (Maybe Text) => Op (GetPresetFile ()) NativeFileChooser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.NativeFileChooser

Methods

runOp :: GetPresetFile () -> orig -> Ref NativeFileChooser -> impl Source #

impl ~ (Text -> IO ()) => Op (SetPresetFile ()) NativeFileChooser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.NativeFileChooser

Methods

runOp :: SetPresetFile () -> orig -> Ref NativeFileChooser -> impl Source #

impl ~ IO AtIndex => Op (GetFilterValue ()) NativeFileChooser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.NativeFileChooser

Methods

runOp :: GetFilterValue () -> orig -> Ref NativeFileChooser -> impl Source #

impl ~ (AtIndex -> IO ()) => Op (SetFilterValue ()) NativeFileChooser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.NativeFileChooser

Methods

runOp :: SetFilterValue () -> orig -> Ref NativeFileChooser -> impl Source #

impl ~ IO Int => Op (Filters ()) NativeFileChooser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.NativeFileChooser

Methods

runOp :: Filters () -> orig -> Ref NativeFileChooser -> impl Source #

impl ~ (Text -> IO ()) => Op (SetFilter ()) FileBrowser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.FileBrowser

Methods

runOp :: SetFilter () -> orig -> Ref FileBrowser -> impl Source #

impl ~ (Text -> IO ()) => Op (SetFilter ()) NativeFileChooser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.NativeFileChooser

Methods

runOp :: SetFilter () -> orig -> Ref NativeFileChooser -> impl Source #

impl ~ IO Text => Op (GetFilter ()) FileBrowser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.FileBrowser

Methods

runOp :: GetFilter () -> orig -> Ref FileBrowser -> impl Source #

impl ~ IO (Maybe Text) => Op (GetFilter ()) NativeFileChooser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.NativeFileChooser

Methods

runOp :: GetFilter () -> orig -> Ref NativeFileChooser -> impl Source #

impl ~ IO (Maybe Text) => Op (GetTitle ()) NativeFileChooser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.NativeFileChooser

Methods

runOp :: GetTitle () -> orig -> Ref NativeFileChooser -> impl Source #

impl ~ (Text -> IO ()) => Op (SetTitle ()) NativeFileChooser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.NativeFileChooser

Methods

runOp :: SetTitle () -> orig -> Ref NativeFileChooser -> impl Source #

impl ~ IO (Maybe Text) => Op (GetDirectory ()) NativeFileChooser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.NativeFileChooser

Methods

runOp :: GetDirectory () -> orig -> Ref NativeFileChooser -> impl Source #

impl ~ (Text -> IO ()) => Op (SetDirectory ()) NativeFileChooser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.NativeFileChooser

Methods

runOp :: SetDirectory () -> orig -> Ref NativeFileChooser -> impl Source #

impl ~ (AtIndex -> IO (Maybe Text)) => Op (GetFilenameAt ()) NativeFileChooser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.NativeFileChooser

Methods

runOp :: GetFilenameAt () -> orig -> Ref NativeFileChooser -> impl Source #

impl ~ IO (Maybe Text) => Op (GetFilename ()) NativeFileChooser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.NativeFileChooser

Methods

runOp :: GetFilename () -> orig -> Ref NativeFileChooser -> impl Source #

impl ~ IO [NativeFileChooserOption] => Op (GetOptions ()) NativeFileChooser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.NativeFileChooser

Methods

runOp :: GetOptions () -> orig -> Ref NativeFileChooser -> impl Source #

impl ~ ([NativeFileChooserOption] -> IO ()) => Op (SetOptions ()) NativeFileChooser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.NativeFileChooser

Methods

runOp :: SetOptions () -> orig -> Ref NativeFileChooser -> impl Source #

impl ~ ([KeyBinding] -> IO ()) => Op (ReplaceKeyBindings ()) TextEditor orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextEditor

Methods

runOp :: ReplaceKeyBindings () -> orig -> Ref TextEditor -> impl Source #

impl ~ IO [KeyBinding] => Op (GetDefaultKeyBindings ()) TextEditor orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextEditor

Methods

runOp :: GetDefaultKeyBindings () -> orig -> Ref TextEditor -> impl Source #

impl ~ IO Bool => Op (GetInsertMode ()) TextEditor orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextEditor

Methods

runOp :: GetInsertMode () -> orig -> Ref TextEditor -> impl Source #

impl ~ (Bool -> IO ()) => Op (SetInsertMode ()) TextEditor orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextEditor

Methods

runOp :: SetInsertMode () -> orig -> Ref TextEditor -> impl Source #

impl ~ (WrapType -> IO ()) => Op (WrapMode ()) TextDisplay orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextDisplay

Methods

runOp :: WrapMode () -> orig -> Ref TextDisplay -> impl Source #

impl ~ IO Text => Op (GetLinenumberFormat ()) TextDisplay orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextDisplay

Methods

runOp :: GetLinenumberFormat () -> orig -> Ref TextDisplay -> impl Source #

impl ~ (Text -> IO ()) => Op (SetLinenumberFormat ()) TextDisplay orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextDisplay

Methods

runOp :: SetLinenumberFormat () -> orig -> Ref TextDisplay -> impl Source #

impl ~ IO AlignType => Op (GetLinenumberAlign ()) TextDisplay orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextDisplay

Methods

runOp :: GetLinenumberAlign () -> orig -> Ref TextDisplay -> impl Source #

impl ~ (AlignType -> IO ()) => Op (SetLinenumberAlign ()) TextDisplay orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextDisplay

Methods

runOp :: SetLinenumberAlign () -> orig -> Ref TextDisplay -> impl Source #

impl ~ IO Color => Op (GetLinenumberBgcolor ()) TextDisplay orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextDisplay

Methods

runOp :: GetLinenumberBgcolor () -> orig -> Ref TextDisplay -> impl Source #

impl ~ (Color -> IO ()) => Op (SetLinenumberBgcolor ()) TextDisplay orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextDisplay

Methods

runOp :: SetLinenumberBgcolor () -> orig -> Ref TextDisplay -> impl Source #

impl ~ IO Color => Op (GetLinenumberFgcolor ()) TextDisplay orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextDisplay

Methods

runOp :: GetLinenumberFgcolor () -> orig -> Ref TextDisplay -> impl Source #

impl ~ (Color -> IO ()) => Op (SetLinenumberFgcolor ()) TextDisplay orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextDisplay

Methods

runOp :: SetLinenumberFgcolor () -> orig -> Ref TextDisplay -> impl Source #

impl ~ IO FontSize => Op (GetLinenumberSize ()) TextDisplay orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextDisplay

Methods

runOp :: GetLinenumberSize () -> orig -> Ref TextDisplay -> impl Source #

impl ~ (FontSize -> IO ()) => Op (SetLinenumberSize ()) TextDisplay orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextDisplay

Methods

runOp :: SetLinenumberSize () -> orig -> Ref TextDisplay -> impl Source #

impl ~ IO Font => Op (GetLinenumberFont ()) TextDisplay orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextDisplay

Methods

runOp :: GetLinenumberFont () -> orig -> Ref TextDisplay -> impl Source #

impl ~ (Font -> IO ()) => Op (SetLinenumberFont ()) TextDisplay orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextDisplay

Methods

runOp :: SetLinenumberFont () -> orig -> Ref TextDisplay -> impl Source #

impl ~ IO Width => Op (GetLinenumberWidth ()) TextDisplay orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextDisplay

Methods

runOp :: GetLinenumberWidth () -> orig -> Ref TextDisplay -> impl Source #

impl ~ (Width -> IO ()) => Op (SetLinenumberWidth ()) TextDisplay orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextDisplay

Methods

runOp :: SetLinenumberWidth () -> orig -> Ref TextDisplay -> impl Source #

impl ~ (Double -> IO Double) => Op (ColToX ()) TextDisplay orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextDisplay

Methods

runOp :: ColToX () -> orig -> Ref TextDisplay -> impl Source #

impl ~ (Double -> IO Double) => Op (XToCol ()) TextDisplay orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextDisplay

Methods

runOp :: XToCol () -> orig -> Ref TextDisplay -> impl Source #

impl ~ (AtIndex -> Int -> LineNumber -> IO TextDisplayStyle) => Op (PositionStyle ()) TextDisplay orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextDisplay

Methods

runOp :: PositionStyle () -> orig -> Ref TextDisplay -> impl Source #

(Parent a TextBuffer, impl ~ (Ref a -> [(Char, StyleTableEntry)] -> Maybe (Char, UnfinishedStyleCb) -> IO ())) => Op (HighlightData ()) TextDisplay orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextDisplay

Methods

runOp :: HighlightData () -> orig -> Ref TextDisplay -> impl Source #

impl ~ (AlignType -> IO ()) => Op (SetScrollbarAlign ()) TextDisplay orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextDisplay

Methods

runOp :: SetScrollbarAlign () -> orig -> Ref TextDisplay -> impl Source #

impl ~ IO AlignType => Op (GetScrollbarAlign ()) TextDisplay orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextDisplay

Methods

runOp :: GetScrollbarAlign () -> orig -> Ref TextDisplay -> impl Source #

impl ~ (CursorType -> IO ()) => Op (SetCursorStyle ()) TextDisplay orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextDisplay

Methods

runOp :: SetCursorStyle () -> orig -> Ref TextDisplay -> impl Source #

impl ~ (Bool -> IO ()) => Op (ShowCursor ()) TextDisplay orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextDisplay

Methods

runOp :: ShowCursor () -> orig -> Ref TextDisplay -> impl Source #

impl ~ IO () => Op (PreviousWord ()) TextDisplay orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextDisplay

Methods

runOp :: PreviousWord () -> orig -> Ref TextDisplay -> impl Source #

impl ~ IO () => Op (NextWord ()) TextDisplay orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextDisplay

Methods

runOp :: NextWord () -> orig -> Ref TextDisplay -> impl Source #

impl ~ IO (Either OutOfRange ()) => Op (MoveDown ()) TextDisplay orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextDisplay

Methods

runOp :: MoveDown () -> orig -> Ref TextDisplay -> impl Source #

impl ~ IO (Either OutOfRange ()) => Op (MoveUp ()) TextDisplay orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextDisplay

Methods

runOp :: MoveUp () -> orig -> Ref TextDisplay -> impl Source #

impl ~ IO (Either OutOfRange ()) => Op (MoveLeft ()) TextDisplay orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextDisplay

Methods

runOp :: MoveLeft () -> orig -> Ref TextDisplay -> impl Source #

impl ~ IO (Either OutOfRange ()) => Op (MoveRight ()) TextDisplay orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextDisplay

Methods

runOp :: MoveRight () -> orig -> Ref TextDisplay -> impl Source #

impl ~ IO () => Op (ShowInsertPosition ()) TextDisplay orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextDisplay

Methods

runOp :: ShowInsertPosition () -> orig -> Ref TextDisplay -> impl Source #

impl ~ (Position -> IO Bool) => Op (InSelection ()) TextDisplay orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextDisplay

Methods

runOp :: InSelection () -> orig -> Ref TextDisplay -> impl Source #

impl ~ (AtIndex -> IO (Either OutOfRange Position)) => Op (PositionToXy ()) TextDisplay orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextDisplay

Methods

runOp :: PositionToXy () -> orig -> Ref TextDisplay -> impl Source #

impl ~ IO AtIndex => Op (GetInsertPosition ()) TextDisplay orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextDisplay

Methods

runOp :: GetInsertPosition () -> orig -> Ref TextDisplay -> impl Source #

impl ~ (AtIndex -> IO ()) => Op (SetInsertPosition ()) TextDisplay orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextDisplay

Methods

runOp :: SetInsertPosition () -> orig -> Ref TextDisplay -> impl Source #

impl ~ (Text -> IO ()) => Op (Overstrike ()) TextDisplay orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextDisplay

Methods

runOp :: Overstrike () -> orig -> Ref TextDisplay -> impl Source #

impl ~ (LineNumber -> AtIndex -> IO ()) => Op (Scroll ()) TextDisplay orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextDisplay

Methods

runOp :: Scroll () -> orig -> Ref TextDisplay -> impl Source #

impl ~ (IndexRange -> IO ()) => Op (RedisplayRange ()) TextDisplay orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextDisplay

Methods

runOp :: RedisplayRange () -> orig -> Ref TextDisplay -> impl Source #

impl ~ IO (Maybe (Ref TextBuffer)) => Op (GetBuffer ()) TextDisplay orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextDisplay

Methods

runOp :: GetBuffer () -> orig -> Ref TextDisplay -> impl Source #

(Parent a TextBuffer, impl ~ (Maybe (Ref a) -> IO ())) => Op (SetBuffer ()) TextDisplay orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextDisplay

Methods

runOp :: SetBuffer () -> orig -> Ref TextDisplay -> impl Source #

impl ~ (AtIndex -> IO (Either OutOfRange AtIndex)) => Op (Utf8Align ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: Utf8Align () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (AtIndex -> IO AtIndex) => Op (NextCharClipped ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: NextCharClipped () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (AtIndex -> IO AtIndex) => Op (NextChar ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: NextChar () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (AtIndex -> IO (Either OutOfRange AtIndex)) => Op (PrevCharClipped ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: PrevCharClipped () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (AtIndex -> IO (Either OutOfRange AtIndex)) => Op (PrevChar ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: PrevChar () -> orig -> Ref TextBuffer -> impl Source #

impl ~ IO (Maybe (Ref TextSelection)) => Op (HighlightSelection ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: HighlightSelection () -> orig -> Ref TextBuffer -> impl Source #

impl ~ IO (Maybe (Ref TextSelection)) => Op (SecondarySelection ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: SecondarySelection () -> orig -> Ref TextBuffer -> impl Source #

impl ~ IO (Maybe (Ref TextSelection)) => Op (PrimarySelection ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: PrimarySelection () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (AtIndex -> Text -> Bool -> IO (Either NotFound AtIndex)) => Op (SearchBackwardWithMatchcase ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: SearchBackwardWithMatchcase () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (AtIndex -> Text -> Bool -> IO (Either NotFound AtIndex)) => Op (SearchForwardWithMatchcase ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: SearchForwardWithMatchcase () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (AtIndex -> Char -> IO (Either NotFound AtIndex)) => Op (FindcharBackward ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: FindcharBackward () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (AtIndex -> Char -> IO (Either NotFound AtIndex)) => Op (FindcharForward ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: FindcharForward () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (AtIndex -> Int -> IO AtIndex) => Op (RewindLines ()) TextDisplay orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextDisplay

Methods

runOp :: RewindLines () -> orig -> Ref TextDisplay -> impl Source #

impl ~ (AtIndex -> Lines -> IO AtIndex) => Op (RewindLines ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: RewindLines () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (AtIndex -> Int -> Bool -> IO AtIndex) => Op (SkipLines ()) TextDisplay orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextDisplay

Methods

runOp :: SkipLines () -> orig -> Ref TextDisplay -> impl Source #

impl ~ (AtIndex -> Lines -> IO AtIndex) => Op (SkipLines ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: SkipLines () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (IndexRange -> Bool -> IO Int) => Op (CountLines ()) TextDisplay orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextDisplay

Methods

runOp :: CountLines () -> orig -> Ref TextDisplay -> impl Source #

impl ~ (IndexRange -> IO Lines) => Op (CountLines ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: CountLines () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (AtIndex -> Int -> IO AtIndex) => Op (SkipDisplayedCharacters ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: SkipDisplayedCharacters () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (IndexRange -> IO Int) => Op (CountDisplayedCharacters ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: CountDisplayedCharacters () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (AtIndex -> IO AtIndex) => Op (WordEnd ()) TextDisplay orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextDisplay

Methods

runOp :: WordEnd () -> orig -> Ref TextDisplay -> impl Source #

impl ~ (AtIndex -> IO (Either OutOfRange AtIndex)) => Op (WordEnd ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: WordEnd () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (AtIndex -> IO AtIndex) => Op (WordStart ()) TextDisplay orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextDisplay

Methods

runOp :: WordStart () -> orig -> Ref TextDisplay -> impl Source #

impl ~ (AtIndex -> IO (Either OutOfRange AtIndex)) => Op (WordStart ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: WordStart () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (AtIndex -> Bool -> IO AtIndex) => Op (LineEnd ()) TextDisplay orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextDisplay

Methods

runOp :: LineEnd () -> orig -> Ref TextDisplay -> impl Source #

impl ~ (LineNumber -> IO (Either OutOfRange AtIndex)) => Op (LineEnd ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: LineEnd () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (AtIndex -> IO AtIndex) => Op (LineStart ()) TextDisplay orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextDisplay

Methods

runOp :: LineStart () -> orig -> Ref TextDisplay -> impl Source #

impl ~ (LineNumber -> IO (Either OutOfRange AtIndex)) => Op (LineStart ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: LineStart () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (LineNumber -> IO (Either OutOfRange String)) => Op (LineText ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: LineText () -> orig -> Ref TextBuffer -> impl Source #

impl ~ IO () => Op (CallPredeleteCallbacks ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: CallPredeleteCallbacks () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (FunPtr () -> IO ()) => Op (RemovePredeleteCallback ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: RemovePredeleteCallback () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (TextPredeleteCb -> IO (FunPtr ())) => Op (AddPredeleteCallback ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: AddPredeleteCallback () -> orig -> Ref TextBuffer -> impl Source #

impl ~ IO () => Op (CallModifyCallbacks ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: CallModifyCallbacks () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (FunPtr () -> IO ()) => Op (RemoveModifyCallback ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: RemoveModifyCallback () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (TextModifyCb -> IO (FunPtr ())) => Op (AddModifyCallback ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: AddModifyCallback () -> orig -> Ref TextBuffer -> impl Source #

impl ~ IO Text => Op (HighlightText ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: HighlightText () -> orig -> Ref TextBuffer -> impl Source #

impl ~ IO (Maybe IndexRange) => Op (HighlightPosition ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: HighlightPosition () -> orig -> Ref TextBuffer -> impl Source #

impl ~ IO () => Op (Unhighlight ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: Unhighlight () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (IndexRange -> IO ()) => Op (SetHighlight ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: SetHighlight () -> orig -> Ref TextBuffer -> impl Source #

impl ~ IO Bool => Op (GetHighlight ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: GetHighlight () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (Text -> IO ()) => Op (ReplaceSecondarySelection ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: ReplaceSecondarySelection () -> orig -> Ref TextBuffer -> impl Source #

impl ~ IO () => Op (RemoveSecondarySelection ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: RemoveSecondarySelection () -> orig -> Ref TextBuffer -> impl Source #

impl ~ IO Text => Op (SecondarySelectionText ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: SecondarySelectionText () -> orig -> Ref TextBuffer -> impl Source #

impl ~ IO IndexRange => Op (SecondarySelectionPosition ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: SecondarySelectionPosition () -> orig -> Ref TextBuffer -> impl Source #

impl ~ IO () => Op (SecondaryUnselect ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: SecondaryUnselect () -> orig -> Ref TextBuffer -> impl Source #

impl ~ IO Bool => Op (SecondarySelected ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: SecondarySelected () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (IndexRange -> IO ()) => Op (SecondarySelect ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: SecondarySelect () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (Text -> IO ()) => Op (ReplaceSelection ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: ReplaceSelection () -> orig -> Ref TextBuffer -> impl Source #

impl ~ IO () => Op (RemoveSelection ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: RemoveSelection () -> orig -> Ref TextBuffer -> impl Source #

impl ~ IO Text => Op (SelectionText ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: SelectionText () -> orig -> Ref TextBuffer -> impl Source #

impl ~ IO IndexRange => Op (SelectionPosition ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: SelectionPosition () -> orig -> Ref TextBuffer -> impl Source #

impl ~ IO () => Op (Unselect ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: Unselect () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (Int -> IO ()) => Op (SetTabDistance ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: SetTabDistance () -> orig -> Ref TextBuffer -> impl Source #

impl ~ IO Int => Op (GetTabDistance ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: GetTabDistance () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (Text -> Int -> IO (Either DataProcessingError ())) => Op (SavefileWithBuflen ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: SavefileWithBuflen () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (Text -> IO (Either DataProcessingError ())) => Op (Savefile ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: Savefile () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (Text -> IndexRange -> Int -> IO (Either DataProcessingError ())) => Op (OutputfileWithBuflen ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: OutputfileWithBuflen () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (Text -> IndexRange -> IO (Either DataProcessingError ())) => Op (Outputfile ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: Outputfile () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (Text -> Int -> IO (Either DataProcessingError ())) => Op (LoadfileWithBuflen ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: LoadfileWithBuflen () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (Text -> IO (Either DataProcessingError ())) => Op (Loadfile ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: Loadfile () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (Text -> Int -> IO (Either DataProcessingError ())) => Op (AppendfileWithBuflen ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: AppendfileWithBuflen () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (Text -> IO (Either DataProcessingError ())) => Op (Appendfile ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: Appendfile () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (Text -> AtIndex -> Int -> IO (Either DataProcessingError ())) => Op (InsertfileWithBuflen ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: InsertfileWithBuflen () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (Text -> AtIndex -> IO (Either DataProcessingError ())) => Op (Insertfile ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: Insertfile () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (Bool -> IO ()) => Op (CanUndo ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: CanUndo () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (Text -> IO ()) => Op (AppendToBuffer ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: AppendToBuffer () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (AtIndex -> IO Char) => Op (ByteAt ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: ByteAt () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (AtIndex -> IO Char) => Op (CharAt ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: CharAt () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (IndexRange -> IO Text) => Op (TextRange ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: TextRange () -> orig -> Ref TextBuffer -> impl Source #

impl ~ IO Int => Op (GetLength ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: GetLength () -> orig -> Ref TextBuffer -> impl Source #

impl ~ IO Text => Op (FileEncodingWarningMessage ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: FileEncodingWarningMessage () -> orig -> Ref TextBuffer -> impl Source #

impl ~ IO Bool => Op (InputFileWasTranscoded ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: InputFileWasTranscoded () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (AtIndex -> IO Bool) => Op (Includes ()) TextSelection orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextSelection

Methods

runOp :: Includes () -> orig -> Ref TextSelection -> impl Source #

impl ~ (Bool -> IO ()) => Op (SetSelected ()) TextSelection orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextSelection

Methods

runOp :: SetSelected () -> orig -> Ref TextSelection -> impl Source #

impl ~ IO AtIndex => Op (Start ()) TextSelection orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextSelection

Methods

runOp :: Start () -> orig -> Ref TextSelection -> impl Source #

impl ~ (AtIndex -> Int -> Int -> IO ()) => Op (Update ()) TextSelection orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextSelection

Methods

runOp :: Update () -> orig -> Ref TextSelection -> impl Source #

impl ~ IO [TreeItemDrawMode] => Op (GetItemDrawMode ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: GetItemDrawMode () -> orig -> Ref Tree -> impl Source #

impl ~ IO [TreeItemDrawMode] => Op (GetItemDrawMode ()) TreePrefs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreePrefs

Methods

runOp :: GetItemDrawMode () -> orig -> Ref TreePrefs -> impl Source #

impl ~ ([TreeItemDrawMode] -> IO ()) => Op (SetItemDrawMode ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: SetItemDrawMode () -> orig -> Ref Tree -> impl Source #

impl ~ ([TreeItemDrawMode] -> IO ()) => Op (SetItemDrawMode ()) TreePrefs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreePrefs

Methods

runOp :: SetItemDrawMode () -> orig -> Ref TreePrefs -> impl Source #

impl ~ IO TreeItemReselectMode => Op (GetItemReselectMode ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: GetItemReselectMode () -> orig -> Ref Tree -> impl Source #

impl ~ IO TreeItemReselectMode => Op (GetItemReselectMode ()) TreePrefs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreePrefs

Methods

runOp :: GetItemReselectMode () -> orig -> Ref TreePrefs -> impl Source #

impl ~ (TreeItemReselectMode -> IO ()) => Op (SetItemReselectMode ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: SetItemReselectMode () -> orig -> Ref Tree -> impl Source #

impl ~ (TreeItemReselectMode -> IO ()) => Op (SetItemReselectMode ()) TreePrefs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreePrefs

Methods

runOp :: SetItemReselectMode () -> orig -> Ref TreePrefs -> impl Source #

impl ~ IO Int => Op (GetWidgetmarginleft ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: GetWidgetmarginleft () -> orig -> Ref Tree -> impl Source #

impl ~ IO Int => Op (GetWidgetmarginleft ()) TreePrefs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreePrefs

Methods

runOp :: GetWidgetmarginleft () -> orig -> Ref TreePrefs -> impl Source #

impl ~ (Int -> IO ()) => Op (SetWidgetmarginleft ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: SetWidgetmarginleft () -> orig -> Ref Tree -> impl Source #

impl ~ (Int -> IO ()) => Op (SetWidgetmarginleft ()) TreePrefs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreePrefs

Methods

runOp :: SetWidgetmarginleft () -> orig -> Ref TreePrefs -> impl Source #

impl ~ IO Int => Op (GetMarginbottom ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: GetMarginbottom () -> orig -> Ref Tree -> impl Source #

impl ~ IO Int => Op (GetMarginbottom ()) TreePrefs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreePrefs

Methods

runOp :: GetMarginbottom () -> orig -> Ref TreePrefs -> impl Source #

impl ~ (Int -> IO ()) => Op (SetMarginbottom ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: SetMarginbottom () -> orig -> Ref Tree -> impl Source #

impl ~ (Int -> IO ()) => Op (SetMarginbottom ()) TreePrefs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreePrefs

Methods

runOp :: SetMarginbottom () -> orig -> Ref TreePrefs -> impl Source #

impl ~ IO () => Op (RecalcTree ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: RecalcTree () -> orig -> Ref Tree -> impl Source #

impl ~ IO TreeReasonType => Op (GetCallbackReason ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: GetCallbackReason () -> orig -> Ref Tree -> impl Source #

impl ~ (TreeReasonType -> IO ()) => Op (SetCallbackReason ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: SetCallbackReason () -> orig -> Ref Tree -> impl Source #

impl ~ IO (Maybe (Ref TreeItem)) => Op (GetCallbackItem ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: GetCallbackItem () -> orig -> Ref Tree -> impl Source #

(Parent a TreeItem, impl ~ (Ref a -> IO ())) => Op (SetCallbackItem ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: SetCallbackItem () -> orig -> Ref Tree -> impl Source #

impl ~ IO Bool => Op (IsVscrollVisible ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: IsVscrollVisible () -> orig -> Ref Tree -> impl Source #

(Parent a Widget, impl ~ (Ref a -> IO Bool)) => Op (IsScrollbar ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: IsScrollbar () -> orig -> Ref Tree -> impl Source #

impl ~ (Int -> IO ()) => Op (SetVposition ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: SetVposition () -> orig -> Ref Tree -> impl Source #

impl ~ IO Int => Op (GetVposition ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: GetVposition () -> orig -> Ref Tree -> impl Source #

impl ~ (Ref TreeItem -> IO ()) => Op (Display ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: Display () -> orig -> Ref Tree -> impl Source #

impl ~ (Ref TreeItem -> IO ()) => Op (ShowItemBottom ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: ShowItemBottom () -> orig -> Ref Tree -> impl Source #

impl ~ (Ref TreeItem -> IO ()) => Op (ShowItemMiddle ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: ShowItemMiddle () -> orig -> Ref Tree -> impl Source #

impl ~ (Ref TreeItem -> IO ()) => Op (ShowItemTop ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: ShowItemTop () -> orig -> Ref Tree -> impl Source #

impl ~ (Ref TreeItem -> Maybe Y -> IO ()) => Op (ShowItemWithYoff ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: ShowItemWithYoff () -> orig -> Ref Tree -> impl Source #

impl ~ IO TreeSelect => Op (Selectmode ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: Selectmode () -> orig -> Ref Tree -> impl Source #

impl ~ IO Color => Op (GetItemLabelfgcolor ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: GetItemLabelfgcolor () -> orig -> Ref Tree -> impl Source #

impl ~ (Font -> IO ()) => Op (SetItemLabelfont ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: SetItemLabelfont () -> orig -> Ref Tree -> impl Source #

impl ~ (Font -> IO ()) => Op (SetItemLabelfont ()) TreePrefs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreePrefs

Methods

runOp :: SetItemLabelfont () -> orig -> Ref TreePrefs -> impl Source #

impl ~ IO (Maybe (Ref TreeItem)) => Op (GetItemFocus ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: GetItemFocus () -> orig -> Ref Tree -> impl Source #

impl ~ (Ref TreeItem -> IO ()) => Op (SetItemFocus ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: SetItemFocus () -> orig -> Ref Tree -> impl Source #

impl ~ (Maybe (Ref TreeItem) -> Bool -> IO ()) => Op (DeselectAllAndCallback ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: DeselectAllAndCallback () -> orig -> Ref Tree -> impl Source #

impl ~ (Maybe (Ref TreeItem) -> Bool -> IO ()) => Op (SelectAllAndCallback ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: SelectAllAndCallback () -> orig -> Ref Tree -> impl Source #

impl ~ (Ref TreeItem -> Bool -> IO ()) => Op (SelectToggleAndCallback ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: SelectToggleAndCallback () -> orig -> Ref Tree -> impl Source #

impl ~ (TreeItemLocator -> Bool -> IO ()) => Op (SelectAndCallback ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: SelectAndCallback () -> orig -> Ref Tree -> impl Source #

impl ~ (TreeItemLocator -> Bool -> IO ()) => Op (CloseAndCallback ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: CloseAndCallback () -> orig -> Ref Tree -> impl Source #

impl ~ (Ref TreeItem -> Bool -> IO ()) => Op (OpenToggleAndCallback ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: OpenToggleAndCallback () -> orig -> Ref Tree -> impl Source #

impl ~ (TreeItemLocator -> Bool -> IO ()) => Op (OpenAndCallback ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: OpenAndCallback () -> orig -> Ref Tree -> impl Source #

impl ~ (Ref TreeItem -> Maybe SearchDirection -> IO (Maybe (Ref TreeItem))) => Op (NextSelectedItemAfterItem ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: NextSelectedItemAfterItem () -> orig -> Ref Tree -> impl Source #

impl ~ IO (Maybe (Ref TreeItem)) => Op (NextSelectedItem ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: NextSelectedItem () -> orig -> Ref Tree -> impl Source #

impl ~ IO (Maybe (Ref TreeItem)) => Op (LastSelectedItem ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: LastSelectedItem () -> orig -> Ref Tree -> impl Source #

impl ~ IO (Maybe (Ref TreeItem)) => Op (FirstSelectedItem ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: FirstSelectedItem () -> orig -> Ref Tree -> impl Source #

impl ~ IO (Maybe (Ref TreeItem)) => Op (LastVisible ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: LastVisible () -> orig -> Ref Tree -> impl Source #

impl ~ IO (Maybe (Ref TreeItem)) => Op (GetLast ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: GetLast () -> orig -> Ref Tree -> impl Source #

impl ~ (Ref TreeItem -> IO (Maybe (Ref TreeItem))) => Op (PrevBeforeItem ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: PrevBeforeItem () -> orig -> Ref Tree -> impl Source #

impl ~ (Ref TreeItem -> Maybe SearchDirection -> Bool -> IO (Maybe (Ref TreeItem))) => Op (NextItem ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: NextItem () -> orig -> Ref Tree -> impl Source #

impl ~ (Ref TreeItem -> IO (Maybe (Ref TreeItem))) => Op (NextAfterItem ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: NextAfterItem () -> orig -> Ref Tree -> impl Source #

impl ~ IO (Maybe (Ref TreeItem)) => Op (FirstVisible ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: FirstVisible () -> orig -> Ref Tree -> impl Source #

impl ~ IO (Maybe (Ref TreeItem)) => Op (ItemClicked ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: ItemClicked () -> orig -> Ref Tree -> impl Source #

impl ~ IO (Maybe (Ref TreeItem)) => Op (Root ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: Root () -> orig -> Ref Tree -> impl Source #

impl ~ (Text -> IO ()) => Op (RootLabel ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: RootLabel () -> orig -> Ref Tree -> impl Source #

impl ~ IO Int => Op (LabelH ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: LabelH () -> orig -> Ref TreeItem -> impl Source #

impl ~ IO Int => Op (LabelW ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: LabelW () -> orig -> Ref TreeItem -> impl Source #

impl ~ IO Int => Op (LabelY ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: LabelY () -> orig -> Ref TreeItem -> impl Source #

impl ~ IO Int => Op (LabelX ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: LabelX () -> orig -> Ref TreeItem -> impl Source #

impl ~ IO Bool => Op (IsRoot ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: IsRoot () -> orig -> Ref TreeItem -> impl Source #

(Parent a TreePrefs, impl ~ (Ref a -> IO Int)) => Op (EventOnLabel ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: EventOnLabel () -> orig -> Ref TreeItem -> impl Source #

(Parent a TreePrefs, impl ~ (Ref a -> IO Int)) => Op (EventOnCollapseIcon ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: EventOnCollapseIcon () -> orig -> Ref TreeItem -> impl Source #

(Parent a TreePrefs, impl ~ (Ref a -> IO (Maybe (Ref TreeItem)))) => Op (FindClicked ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: FindClicked () -> orig -> Ref TreeItem -> impl Source #

impl ~ IO Bool => Op (VisibleR ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: VisibleR () -> orig -> Ref TreeItem -> impl Source #

impl ~ IO Bool => Op (IsVisible ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: IsVisible () -> orig -> Ref TreeItem -> impl Source #

impl ~ IO Bool => Op (IsActive ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: IsActive () -> orig -> Ref TreeItem -> impl Source #

impl ~ (Bool -> IO ()) => Op (ActivateWith ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: ActivateWith () -> orig -> Ref TreeItem -> impl Source #

impl ~ IO () => Op (DeselectAll ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: DeselectAll () -> orig -> Ref Tree -> impl Source #

impl ~ IO Int => Op (DeselectAll ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: DeselectAll () -> orig -> Ref TreeItem -> impl Source #

impl ~ IO () => Op (SelectAll ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: SelectAll () -> orig -> Ref Tree -> impl Source #

impl ~ IO Int => Op (SelectAll ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: SelectAll () -> orig -> Ref TreeItem -> impl Source #

impl ~ (Ref TreeItem -> IO ()) => Op (SelectToggle ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: SelectToggle () -> orig -> Ref Tree -> impl Source #

impl ~ IO () => Op (SelectToggle ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: SelectToggle () -> orig -> Ref TreeItem -> impl Source #

impl ~ (Bool -> IO ()) => Op (SelectSet ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: SelectSet () -> orig -> Ref TreeItem -> impl Source #

impl ~ (Ref TreeItem -> IO ()) => Op (OpenToggle ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: OpenToggle () -> orig -> Ref Tree -> impl Source #

impl ~ IO () => Op (OpenToggle ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: OpenToggle () -> orig -> Ref TreeItem -> impl Source #

impl ~ (TreeItemLocator -> IO Bool) => Op (IsClose ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: IsClose () -> orig -> Ref Tree -> impl Source #

impl ~ IO Bool => Op (IsClose ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: IsClose () -> orig -> Ref TreeItem -> impl Source #

impl ~ (TreeItemLocator -> IO Bool) => Op (IsOpen ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: IsOpen () -> orig -> Ref Tree -> impl Source #

impl ~ IO Bool => Op (IsOpen ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: IsOpen () -> orig -> Ref TreeItem -> impl Source #

impl ~ (TreeItemLocator -> IO ()) => Op (Close ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: Close () -> orig -> Ref Tree -> impl Source #

impl ~ IO () => Op (Close ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: Close () -> orig -> Ref TreeItem -> impl Source #

impl ~ (TreeItemLocator -> IO ()) => Op (Open ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: Open () -> orig -> Ref Tree -> impl Source #

impl ~ IO () => Op (Open ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: Open () -> orig -> Ref TreeItem -> impl Source #

(Parent a TreePrefs, impl ~ (Ref a -> IO (Maybe (Ref TreeItem)))) => Op (PrevDisplayed ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: PrevDisplayed () -> orig -> Ref TreeItem -> impl Source #

(Parent a TreePrefs, impl ~ (Ref a -> IO (Maybe (Ref TreeItem)))) => Op (NextDisplayed ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: NextDisplayed () -> orig -> Ref TreeItem -> impl Source #

impl ~ (AtIndex -> IO ()) => Op (UpdatePrevNext ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: UpdatePrevNext () -> orig -> Ref TreeItem -> impl Source #

impl ~ IO (Maybe (Ref TreeItem)) => Op (PrevSibling ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: PrevSibling () -> orig -> Ref TreeItem -> impl Source #

impl ~ IO (Maybe (Ref TreeItem)) => Op (NextSibling ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: NextSibling () -> orig -> Ref TreeItem -> impl Source #

impl ~ IO Int => Op (GetDepth ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: GetDepth () -> orig -> Ref TreeItem -> impl Source #

(Parent a TreeItem, impl ~ (Ref a -> MoveType -> IO (Either MoveError ()))) => Op (MoveTo ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: MoveTo () -> orig -> Ref TreeItem -> impl Source #

(Parent a TreeItem, impl ~ (Ref a -> AtIndex -> IO (Either UnknownError ()))) => Op (Reparent ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: Reparent () -> orig -> Ref TreeItem -> impl Source #

impl ~ (AtIndex -> IO (Either UnknownError (Ref orig))) => Op (Deparent ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: Deparent () -> orig -> Ref TreeItem -> impl Source #

(Parent a TreeItem, impl ~ (Ref a -> Text -> IO (Maybe (Ref a)))) => Op (InsertAbove ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: InsertAbove () -> orig -> Ref Tree -> impl Source #

(Parent a TreePrefs, impl ~ (Ref a -> Text -> IO (Maybe (Ref TreeItem)))) => Op (InsertAbove ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: InsertAbove () -> orig -> Ref TreeItem -> impl Source #

(Parent a TreeItem, impl ~ (Text -> Ref a -> IO (Maybe (Ref TreeItem)))) => Op (AddAt ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: AddAt () -> orig -> Ref Tree -> impl Source #

(Parent a TreeItem, Parent b TreePrefs, impl ~ (Ref b -> [Text] -> Maybe (Ref a) -> IO (Maybe (Ref a)))) => Op (AddAt ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: AddAt () -> orig -> Ref TreeItem -> impl Source #

impl ~ (Text -> IO (Maybe (Ref TreeItem))) => Op (FindItem ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: FindItem () -> orig -> Ref Tree -> impl Source #

impl ~ ([Text] -> IO (Maybe (Ref TreeItem))) => Op (FindItem ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: FindItem () -> orig -> Ref TreeItem -> impl Source #

impl ~ ([Text] -> IO (Maybe (Ref TreeItem))) => Op (FindInChildren ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: FindInChildren () -> orig -> Ref TreeItem -> impl Source #

(Parent a TreeItem, impl ~ (Ref a -> Ref a -> IO (Either TreeItemNotFound ()))) => Op (SwapChildrenByTreeItem ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: SwapChildrenByTreeItem () -> orig -> Ref TreeItem -> impl Source #

impl ~ (AtIndex -> AtIndex -> IO ()) => Op (SwapChildren ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: SwapChildren () -> orig -> Ref TreeItem -> impl Source #

(Parent a TreeItem, impl ~ (Ref a -> IO ())) => Op (ClearChildren ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: ClearChildren () -> orig -> Ref Tree -> impl Source #

impl ~ IO () => Op (ClearChildren ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: ClearChildren () -> orig -> Ref TreeItem -> impl Source #

impl ~ (TreeItemLocator -> IO (Either UnknownError ())) => Op (RemoveChild ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: RemoveChild () -> orig -> Ref TreeItem -> impl Source #

impl ~ (TreeItemLocator -> IO (Maybe AtIndex)) => Op (FindChild ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: FindChild () -> orig -> Ref TreeItem -> impl Source #

impl ~ IO Bool => Op (HasChildren ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: HasChildren () -> orig -> Ref TreeItem -> impl Source #

impl ~ (AtIndex -> IO (Maybe (Ref Widget))) => Op (Child ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: Child () -> orig -> Ref TreeItem -> impl Source #

impl ~ IO (Maybe (Ref Widget)) => Op (GetWidget ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: GetWidget () -> orig -> Ref TreeItem -> impl Source #

(Parent a Widget, impl ~ (Maybe (Ref a) -> IO ())) => Op (SetWidget ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: SetWidget () -> orig -> Ref TreeItem -> impl Source #

impl ~ IO () => Op (ShowSelf ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: ShowSelf () -> orig -> Ref Tree -> impl Source #

impl ~ (Maybe Text -> IO ()) => Op (ShowSelf ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: ShowSelf () -> orig -> Ref TreeItem -> impl Source #

impl ~ (TreeSelect -> IO ()) => Op (SetSelectmode ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: SetSelectmode () -> orig -> Ref Tree -> impl Source #

impl ~ (TreeSelect -> IO ()) => Op (SetSelectmode ()) TreePrefs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreePrefs

Methods

runOp :: SetSelectmode () -> orig -> Ref TreePrefs -> impl Source #

impl ~ IO TreeSelect => Op (GetSelectmode ()) TreePrefs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreePrefs

Methods

runOp :: GetSelectmode () -> orig -> Ref TreePrefs -> impl Source #

impl ~ (Bool -> IO ()) => Op (SetShowroot ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: SetShowroot () -> orig -> Ref Tree -> impl Source #

impl ~ (Bool -> IO ()) => Op (SetShowroot ()) TreePrefs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreePrefs

Methods

runOp :: SetShowroot () -> orig -> Ref TreePrefs -> impl Source #

impl ~ IO Bool => Op (GetShowroot ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: GetShowroot () -> orig -> Ref Tree -> impl Source #

impl ~ IO Bool => Op (GetShowroot ()) TreePrefs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreePrefs

Methods

runOp :: GetShowroot () -> orig -> Ref TreePrefs -> impl Source #

impl ~ (Boxtype -> IO ()) => Op (SetSelectbox ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: SetSelectbox () -> orig -> Ref Tree -> impl Source #

impl ~ (Boxtype -> IO ()) => Op (SetSelectbox ()) TreePrefs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreePrefs

Methods

runOp :: SetSelectbox () -> orig -> Ref TreePrefs -> impl Source #

impl ~ IO Boxtype => Op (GetSelectbox ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: GetSelectbox () -> orig -> Ref Tree -> impl Source #

impl ~ IO Boxtype => Op (GetSelectbox ()) TreePrefs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreePrefs

Methods

runOp :: GetSelectbox () -> orig -> Ref TreePrefs -> impl Source #

impl ~ (TreeSort -> IO ()) => Op (SetSortorder ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: SetSortorder () -> orig -> Ref Tree -> impl Source #

impl ~ (TreeSort -> IO ()) => Op (SetSortorder ()) TreePrefs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreePrefs

Methods

runOp :: SetSortorder () -> orig -> Ref TreePrefs -> impl Source #

impl ~ IO TreeSort => Op (GetSortorder ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: GetSortorder () -> orig -> Ref Tree -> impl Source #

impl ~ IO TreeSort => Op (GetSortorder ()) TreePrefs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreePrefs

Methods

runOp :: GetSortorder () -> orig -> Ref TreePrefs -> impl Source #

impl ~ (Bool -> IO ()) => Op (SetShowcollapse ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: SetShowcollapse () -> orig -> Ref Tree -> impl Source #

impl ~ (Bool -> IO ()) => Op (SetShowcollapse ()) TreePrefs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreePrefs

Methods

runOp :: SetShowcollapse () -> orig -> Ref TreePrefs -> impl Source #

impl ~ IO Bool => Op (GetShowcollapse ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: GetShowcollapse () -> orig -> Ref Tree -> impl Source #

impl ~ IO Bool => Op (GetShowcollapse ()) TreePrefs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreePrefs

Methods

runOp :: GetShowcollapse () -> orig -> Ref TreePrefs -> impl Source #

(Parent a Image, impl ~ (Maybe (Ref a) -> IO ())) => Op (SetUsericon ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: SetUsericon () -> orig -> Ref Tree -> impl Source #

(Parent a Image, impl ~ (Maybe (Ref a) -> IO ())) => Op (SetUsericon ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: SetUsericon () -> orig -> Ref TreeItem -> impl Source #

(Parent a Image, impl ~ (Maybe (Ref a) -> IO ())) => Op (SetUsericon ()) TreePrefs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreePrefs

Methods

runOp :: SetUsericon () -> orig -> Ref TreePrefs -> impl Source #

impl ~ IO (Maybe (Ref Image)) => Op (GetUsericon ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: GetUsericon () -> orig -> Ref Tree -> impl Source #

impl ~ IO (Maybe (Ref Image)) => Op (GetUsericon ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: GetUsericon () -> orig -> Ref TreeItem -> impl Source #

impl ~ IO (Maybe (Ref Image)) => Op (GetUsericon ()) TreePrefs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreePrefs

Methods

runOp :: GetUsericon () -> orig -> Ref TreePrefs -> impl Source #

(Parent a Image, impl ~ (Maybe (Ref a) -> IO ())) => Op (SetCloseicon ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: SetCloseicon () -> orig -> Ref Tree -> impl Source #

(Parent a Image, impl ~ (Maybe (Ref a) -> IO ())) => Op (SetCloseicon ()) TreePrefs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreePrefs

Methods

runOp :: SetCloseicon () -> orig -> Ref TreePrefs -> impl Source #

impl ~ IO (Maybe (Ref Image)) => Op (GetCloseicon ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: GetCloseicon () -> orig -> Ref Tree -> impl Source #

impl ~ IO (Maybe (Ref Image)) => Op (GetCloseicon ()) TreePrefs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreePrefs

Methods

runOp :: GetCloseicon () -> orig -> Ref TreePrefs -> impl Source #

(Parent a Image, impl ~ (Maybe (Ref a) -> IO ())) => Op (SetOpenicon ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: SetOpenicon () -> orig -> Ref Tree -> impl Source #

(Parent a Image, impl ~ (Maybe (Ref a) -> IO ())) => Op (SetOpenicon ()) TreePrefs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreePrefs

Methods

runOp :: SetOpenicon () -> orig -> Ref TreePrefs -> impl Source #

impl ~ IO (Maybe (Ref Image)) => Op (GetOpenicon ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: GetOpenicon () -> orig -> Ref Tree -> impl Source #

impl ~ IO (Maybe (Ref Image)) => Op (GetOpenicon ()) TreePrefs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreePrefs

Methods

runOp :: GetOpenicon () -> orig -> Ref TreePrefs -> impl Source #

impl ~ (Int -> IO ()) => Op (SetConnectorwidth ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: SetConnectorwidth () -> orig -> Ref Tree -> impl Source #

impl ~ (Int -> IO ()) => Op (SetConnectorwidth ()) TreePrefs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreePrefs

Methods

runOp :: SetConnectorwidth () -> orig -> Ref TreePrefs -> impl Source #

impl ~ IO Int => Op (GetConnectorwidth ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: GetConnectorwidth () -> orig -> Ref Tree -> impl Source #

impl ~ IO Int => Op (GetConnectorwidth ()) TreePrefs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreePrefs

Methods

runOp :: GetConnectorwidth () -> orig -> Ref TreePrefs -> impl Source #

impl ~ (TreeConnector -> IO ()) => Op (SetConnectorstyle ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: SetConnectorstyle () -> orig -> Ref Tree -> impl Source #

impl ~ (TreeConnector -> IO ()) => Op (SetConnectorstyle ()) TreePrefs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreePrefs

Methods

runOp :: SetConnectorstyle () -> orig -> Ref TreePrefs -> impl Source #

impl ~ IO TreeConnector => Op (GetConnectorstyle ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: GetConnectorstyle () -> orig -> Ref Tree -> impl Source #

impl ~ IO TreeConnector => Op (GetConnectorstyle ()) TreePrefs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreePrefs

Methods

runOp :: GetConnectorstyle () -> orig -> Ref TreePrefs -> impl Source #

impl ~ (Color -> IO ()) => Op (SetConnectorcolor ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: SetConnectorcolor () -> orig -> Ref Tree -> impl Source #

impl ~ (Color -> IO ()) => Op (SetConnectorcolor ()) TreePrefs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreePrefs

Methods

runOp :: SetConnectorcolor () -> orig -> Ref TreePrefs -> impl Source #

impl ~ IO Color => Op (GetConnectorcolor ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: GetConnectorcolor () -> orig -> Ref Tree -> impl Source #

impl ~ IO Color => Op (GetConnectorcolor ()) TreePrefs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreePrefs

Methods

runOp :: GetConnectorcolor () -> orig -> Ref TreePrefs -> impl Source #

impl ~ (Int -> IO ()) => Op (SetLinespacing ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: SetLinespacing () -> orig -> Ref Tree -> impl Source #

impl ~ (Int -> IO ()) => Op (SetLinespacing ()) TreePrefs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreePrefs

Methods

runOp :: SetLinespacing () -> orig -> Ref TreePrefs -> impl Source #

impl ~ IO Int => Op (GetLinespacing ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: GetLinespacing () -> orig -> Ref Tree -> impl Source #

impl ~ IO Int => Op (GetLinespacing ()) TreePrefs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreePrefs

Methods

runOp :: GetLinespacing () -> orig -> Ref TreePrefs -> impl Source #

impl ~ (Int -> IO ()) => Op (SetLabelmarginleft ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: SetLabelmarginleft () -> orig -> Ref Tree -> impl Source #

impl ~ (Int -> IO ()) => Op (SetLabelmarginleft ()) TreePrefs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreePrefs

Methods

runOp :: SetLabelmarginleft () -> orig -> Ref TreePrefs -> impl Source #

impl ~ IO Int => Op (GetLabelmarginleft ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: GetLabelmarginleft () -> orig -> Ref Tree -> impl Source #

impl ~ IO Int => Op (GetLabelmarginleft ()) TreePrefs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreePrefs

Methods

runOp :: GetLabelmarginleft () -> orig -> Ref TreePrefs -> impl Source #

impl ~ (Int -> IO ()) => Op (SetUsericonmarginleft ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: SetUsericonmarginleft () -> orig -> Ref Tree -> impl Source #

impl ~ (Int -> IO ()) => Op (SetUsericonmarginleft ()) TreePrefs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreePrefs

Methods

runOp :: SetUsericonmarginleft () -> orig -> Ref TreePrefs -> impl Source #

impl ~ IO Int => Op (GetUsericonmarginleft ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: GetUsericonmarginleft () -> orig -> Ref Tree -> impl Source #

impl ~ IO Int => Op (GetUsericonmarginleft ()) TreePrefs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreePrefs

Methods

runOp :: GetUsericonmarginleft () -> orig -> Ref TreePrefs -> impl Source #

impl ~ (Int -> IO ()) => Op (SetOpenchildMarginbottom ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: SetOpenchildMarginbottom () -> orig -> Ref Tree -> impl Source #

impl ~ (Int -> IO ()) => Op (SetOpenchildMarginbottom ()) TreePrefs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreePrefs

Methods

runOp :: SetOpenchildMarginbottom () -> orig -> Ref TreePrefs -> impl Source #

impl ~ IO Int => Op (GetOpenchildMarginbottom ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: GetOpenchildMarginbottom () -> orig -> Ref Tree -> impl Source #

impl ~ IO Int => Op (GetOpenchildMarginbottom ()) TreePrefs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreePrefs

Methods

runOp :: GetOpenchildMarginbottom () -> orig -> Ref TreePrefs -> impl Source #

impl ~ (Int -> IO ()) => Op (SetMargintop ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: SetMargintop () -> orig -> Ref Tree -> impl Source #

impl ~ (Int -> IO ()) => Op (SetMargintop ()) TreePrefs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreePrefs

Methods

runOp :: SetMargintop () -> orig -> Ref TreePrefs -> impl Source #

impl ~ IO Int => Op (GetMargintop ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: GetMargintop () -> orig -> Ref Tree -> impl Source #

impl ~ IO Int => Op (GetMargintop ()) TreePrefs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreePrefs

Methods

runOp :: GetMargintop () -> orig -> Ref TreePrefs -> impl Source #

impl ~ (Int -> IO ()) => Op (SetMarginleft ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: SetMarginleft () -> orig -> Ref Tree -> impl Source #

impl ~ (Int -> IO ()) => Op (SetMarginleft ()) TreePrefs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreePrefs

Methods

runOp :: SetMarginleft () -> orig -> Ref TreePrefs -> impl Source #

impl ~ IO Int => Op (GetMarginleft ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: GetMarginleft () -> orig -> Ref Tree -> impl Source #

impl ~ IO Int => Op (GetMarginleft ()) TreePrefs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreePrefs

Methods

runOp :: GetMarginleft () -> orig -> Ref TreePrefs -> impl Source #

impl ~ (Color -> IO ()) => Op (SetLabelbgcolor ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: SetLabelbgcolor () -> orig -> Ref TreeItem -> impl Source #

impl ~ (Color -> IO ()) => Op (SetLabelbgcolor ()) TreePrefs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreePrefs

Methods

runOp :: SetLabelbgcolor () -> orig -> Ref TreePrefs -> impl Source #

impl ~ IO Color => Op (GetLabelbgcolor ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: GetLabelbgcolor () -> orig -> Ref TreeItem -> impl Source #

impl ~ IO Color => Op (GetLabelbgcolor ()) TreePrefs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreePrefs

Methods

runOp :: GetLabelbgcolor () -> orig -> Ref TreePrefs -> impl Source #

impl ~ (Color -> IO ()) => Op (SetLabelfgcolor ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: SetLabelfgcolor () -> orig -> Ref TreeItem -> impl Source #

impl ~ (Color -> IO ()) => Op (SetLabelfgcolor ()) TreePrefs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreePrefs

Methods

runOp :: SetLabelfgcolor () -> orig -> Ref TreePrefs -> impl Source #

impl ~ IO Color => Op (GetLabelfgcolor ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: GetLabelfgcolor () -> orig -> Ref TreeItem -> impl Source #

impl ~ IO Color => Op (GetLabelfgcolor ()) TreePrefs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreePrefs

Methods

runOp :: GetLabelfgcolor () -> orig -> Ref TreePrefs -> impl Source #

impl ~ (Color -> IO ()) => Op (SetItemLabelbgcolor ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: SetItemLabelbgcolor () -> orig -> Ref Tree -> impl Source #

impl ~ (Color -> IO ()) => Op (SetItemLabelbgcolor ()) TreePrefs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreePrefs

Methods

runOp :: SetItemLabelbgcolor () -> orig -> Ref TreePrefs -> impl Source #

impl ~ IO Color => Op (GetItemLabelbgcolor ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: GetItemLabelbgcolor () -> orig -> Ref Tree -> impl Source #

impl ~ IO Color => Op (GetItemLabelbgcolor ()) TreePrefs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreePrefs

Methods

runOp :: GetItemLabelbgcolor () -> orig -> Ref TreePrefs -> impl Source #

impl ~ (Color -> IO ()) => Op (SetItemLabelfgcolor ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: SetItemLabelfgcolor () -> orig -> Ref Tree -> impl Source #

impl ~ (Color -> IO ()) => Op (SetItemLabelfgcolor ()) TreePrefs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreePrefs

Methods

runOp :: SetItemLabelfgcolor () -> orig -> Ref TreePrefs -> impl Source #

impl ~ (FontSize -> IO ()) => Op (SetItemLabelsize ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: SetItemLabelsize () -> orig -> Ref Tree -> impl Source #

impl ~ (FontSize -> IO ()) => Op (SetItemLabelsize ()) TreePrefs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreePrefs

Methods

runOp :: SetItemLabelsize () -> orig -> Ref TreePrefs -> impl Source #

impl ~ IO FontSize => Op (GetItemLabelsize ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: GetItemLabelsize () -> orig -> Ref Tree -> impl Source #

impl ~ IO FontSize => Op (GetItemLabelsize ()) TreePrefs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreePrefs

Methods

runOp :: GetItemLabelsize () -> orig -> Ref TreePrefs -> impl Source #

impl ~ IO Font => Op (GetItemLabelfont ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: GetItemLabelfont () -> orig -> Ref Tree -> impl Source #

impl ~ IO Font => Op (GetItemLabelfont ()) TreePrefs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreePrefs

Methods

runOp :: GetItemLabelfont () -> orig -> Ref TreePrefs -> impl Source #

impl ~ (Bool -> IO ()) => Op (SetShadow ()) Clock orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Clock

Methods

runOp :: SetShadow () -> orig -> Ref Clock -> impl Source #

impl ~ IO Bool => Op (GetShadow ()) Clock orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Clock

Methods

runOp :: GetShadow () -> orig -> Ref Clock -> impl Source #

impl ~ IO ClockSinceEpoch => Op (GetValueSinceEpoch ()) Clock orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Clock

Methods

runOp :: GetValueSinceEpoch () -> orig -> Ref Clock -> impl Source #

impl ~ IO () => Op (Sort ()) Browser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Browser

Methods

runOp :: Sort () -> orig -> Ref Browser -> impl Source #

impl ~ (SortType -> IO ()) => Op (SortWithSortType ()) Browser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Browser

Methods

runOp :: SortWithSortType () -> orig -> Ref Browser -> impl Source #

impl ~ (Color -> IO ()) => Op (SetScrollbarSelectionColor ()) Browser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Browser

Methods

runOp :: SetScrollbarSelectionColor () -> orig -> Ref Browser -> impl Source #

impl ~ (Color -> IO ()) => Op (SetScrollbarColor ()) Browser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Browser

Methods

runOp :: SetScrollbarColor () -> orig -> Ref Browser -> impl Source #

impl ~ (Width -> IO ()) => Op (SetScrollbarWidth ()) TextDisplay orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextDisplay

Methods

runOp :: SetScrollbarWidth () -> orig -> Ref TextDisplay -> impl Source #

impl ~ (Int -> IO ()) => Op (SetScrollbarWidth ()) Browser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Browser

Methods

runOp :: SetScrollbarWidth () -> orig -> Ref Browser -> impl Source #

impl ~ IO Width => Op (GetScrollbarWidth ()) TextDisplay orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextDisplay

Methods

runOp :: GetScrollbarWidth () -> orig -> Ref TextDisplay -> impl Source #

impl ~ IO Int => Op (GetScrollbarWidth ()) Browser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Browser

Methods

runOp :: GetScrollbarWidth () -> orig -> Ref Browser -> impl Source #

impl ~ (Int -> IO ()) => Op (SetScrollbarSize ()) Scrolled orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Scrolled

Methods

runOp :: SetScrollbarSize () -> orig -> Ref Scrolled -> impl Source #

impl ~ (Int -> IO ()) => Op (SetScrollbarSize ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: SetScrollbarSize () -> orig -> Ref Tree -> impl Source #

impl ~ (Int -> IO ()) => Op (SetScrollbarSize ()) Browser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Browser

Methods

runOp :: SetScrollbarSize () -> orig -> Ref Browser -> impl Source #

impl ~ IO Int => Op (GetScrollbarSize ()) Scrolled orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Scrolled

Methods

runOp :: GetScrollbarSize () -> orig -> Ref Scrolled -> impl Source #

impl ~ IO Int => Op (GetScrollbarSize ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: GetScrollbarSize () -> orig -> Ref Tree -> impl Source #

impl ~ IO Int => Op (GetScrollbarSize ()) Browser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Browser

Methods

runOp :: GetScrollbarSize () -> orig -> Ref Browser -> impl Source #

impl ~ (ScrollbarMode -> IO ()) => Op (SetHasScrollbar ()) Browser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Browser

Methods

runOp :: SetHasScrollbar () -> orig -> Ref Browser -> impl Source #

impl ~ IO ScrollbarMode => Op (GetHasScrollbar ()) Browser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Browser

Methods

runOp :: GetHasScrollbar () -> orig -> Ref Browser -> impl Source #

impl ~ (PixelPosition -> IO ()) => Op (SetHposition ()) Browser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Browser

Methods

runOp :: SetHposition () -> orig -> Ref Browser -> impl Source #

impl ~ IO PixelPosition => Op (GetHposition ()) Browser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Browser

Methods

runOp :: GetHposition () -> orig -> Ref Browser -> impl Source #

impl ~ (TreeItemLocator -> Bool -> IO ()) => Op (DeselectAndCallback ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: DeselectAndCallback () -> orig -> Ref Tree -> impl Source #

impl ~ IO (Either NoChange ()) => Op (DeselectAndCallback ()) Browser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Browser

Methods

runOp :: DeselectAndCallback () -> orig -> Ref Browser -> impl Source #

impl ~ (TreeItemLocator -> IO (Either NoChange ())) => Op (Deselect ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: Deselect () -> orig -> Ref Tree -> impl Source #

impl ~ IO () => Op (Deselect ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: Deselect () -> orig -> Ref TreeItem -> impl Source #

impl ~ IO (Either NoChange ()) => Op (Deselect ()) Browser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Browser

Methods

runOp :: Deselect () -> orig -> Ref Browser -> impl Source #

impl ~ (Ref TreeItem -> Bool -> IO ()) => Op (SelectOnlyAndCallback ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: SelectOnlyAndCallback () -> orig -> Ref Tree -> impl Source #

impl ~ (Ref TreeItem -> IO ()) => Op (SelectOnly ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: SelectOnly () -> orig -> Ref Tree -> impl Source #

impl ~ (LineNumber -> IO ()) => Op (RemoveIcon ()) Browser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Browser

Methods

runOp :: RemoveIcon () -> orig -> Ref Browser -> impl Source #

impl ~ (LineNumber -> IO ()) => Op (MakeVisible ()) Browser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Browser

Methods

runOp :: MakeVisible () -> orig -> Ref Browser -> impl Source #

impl ~ (Ref TreeItem -> IO Bool) => Op (Displayed ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: Displayed () -> orig -> Ref Tree -> impl Source #

impl ~ (LineNumber -> IO Bool) => Op (Displayed ()) Browser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Browser

Methods

runOp :: Displayed () -> orig -> Ref Browser -> impl Source #

impl ~ ([Int] -> IO ()) => Op (SetColumnWidths ()) Browser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Browser

Methods

runOp :: SetColumnWidths () -> orig -> Ref Browser -> impl Source #

impl ~ IO [Int] => Op (GetColumnWidths ()) Browser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Browser

Methods

runOp :: GetColumnWidths () -> orig -> Ref Browser -> impl Source #

impl ~ (Char -> IO ()) => Op (SetColumnChar ()) Browser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Browser

Methods

runOp :: SetColumnChar () -> orig -> Ref Browser -> impl Source #

impl ~ IO Char => Op (GetColumnChar ()) Browser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Browser

Methods

runOp :: GetColumnChar () -> orig -> Ref Browser -> impl Source #

impl ~ (Char -> IO ()) => Op (SetFormatChar ()) Browser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Browser

Methods

runOp :: SetFormatChar () -> orig -> Ref Browser -> impl Source #

impl ~ IO Char => Op (GetFormatChar ()) Browser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Browser

Methods

runOp :: GetFormatChar () -> orig -> Ref Browser -> impl Source #

impl ~ (Text -> IO ()) => Op (SetText ()) SimpleTerminal orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.SimpleTerminal

Methods

runOp :: SetText () -> orig -> Ref SimpleTerminal -> impl Source #

impl ~ (Text -> IO ()) => Op (SetText ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: SetText () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (LineNumber -> Text -> IO ()) => Op (SetText ()) Browser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Browser

Methods

runOp :: SetText () -> orig -> Ref Browser -> impl Source #

impl ~ (LineNumber -> IO ()) => Op (HideLine ()) Browser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Browser

Methods

runOp :: HideLine () -> orig -> Ref Browser -> impl Source #

impl ~ (LineNumber -> IO ()) => Op (ShowWidgetLine ()) Browser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Browser

Methods

runOp :: ShowWidgetLine () -> orig -> Ref Browser -> impl Source #

impl ~ IO Bool => Op (Selected ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: Selected () -> orig -> Ref TextBuffer -> impl Source #

impl ~ IO Bool => Op (Selected ()) TextSelection orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextSelection

Methods

runOp :: Selected () -> orig -> Ref TextSelection -> impl Source #

impl ~ (LineNumber -> IO Bool) => Op (Selected ()) Browser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Browser

Methods

runOp :: Selected () -> orig -> Ref Browser -> impl Source #

impl ~ (IndexRange -> IO ()) => Op (Select ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: Select () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (TreeItemLocator -> IO (Either NoChange ())) => Op (Select ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: Select () -> orig -> Ref Tree -> impl Source #

impl ~ IO () => Op (Select ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: Select () -> orig -> Ref TreeItem -> impl Source #

impl ~ (LineNumber -> Bool -> IO (Either NoChange ())) => Op (Select ()) Browser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Browser

Methods

runOp :: Select () -> orig -> Ref Browser -> impl Source #

impl ~ (LineNumber -> IO ()) => Op (SetMiddleline ()) Browser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Browser

Methods

runOp :: SetMiddleline () -> orig -> Ref Browser -> impl Source #

impl ~ (LineNumber -> IO ()) => Op (SetBottomline ()) Browser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Browser

Methods

runOp :: SetBottomline () -> orig -> Ref Browser -> impl Source #

impl ~ (LineNumber -> IO ()) => Op (SetTopline ()) Browser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Browser

Methods

runOp :: SetTopline () -> orig -> Ref Browser -> impl Source #

impl ~ (LineNumber -> LinePosition -> IO ()) => Op (Lineposition ()) Browser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Browser

Methods

runOp :: Lineposition () -> orig -> Ref Browser -> impl Source #

impl ~ IO LineNumber => Op (GetTopline ()) Browser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Browser

Methods

runOp :: GetTopline () -> orig -> Ref Browser -> impl Source #

impl ~ (LineNumber -> LineNumber -> IO ()) => Op (Swap ()) Browser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Browser

Methods

runOp :: Swap () -> orig -> Ref Browser -> impl Source #

impl ~ (Text -> FileSortF -> IO (Either UnknownError ())) => Op (Load ()) FileBrowser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.FileBrowser

Methods

runOp :: Load () -> orig -> Ref FileBrowser -> impl Source #

impl ~ (Text -> IO (Either UnknownError ())) => Op (Load ()) Browser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Browser

Methods

runOp :: Load () -> orig -> Ref Browser -> impl Source #

impl ~ (AtIndex -> AtIndex -> IO (Either OutOfRange ())) => Op (Move ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: Move () -> orig -> Ref TreeItem -> impl Source #

impl ~ (LineNumber -> LineNumber -> IO ()) => Op (Move ()) Browser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Browser

Methods

runOp :: Move () -> orig -> Ref Browser -> impl Source #

impl ~ IO Int => Op (PixelW ()) GlWindow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.GlWindow

Methods

runOp :: PixelW () -> orig -> Ref GlWindow -> impl Source #

impl ~ IO Int => Op (PixelH ()) GlWindow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.GlWindow

Methods

runOp :: PixelH () -> orig -> Ref GlWindow -> impl Source #

impl ~ IO Float => Op (PixelsPerUnit ()) GlWindow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.GlWindow

Methods

runOp :: PixelsPerUnit () -> orig -> Ref GlWindow -> impl Source #

impl ~ IO () => Op (MakeOverlayCurrent ()) GlWindow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.GlWindow

Methods

runOp :: MakeOverlayCurrent () -> orig -> Ref GlWindow -> impl Source #

impl ~ IO () => Op (HideOverlay ()) GlWindow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.GlWindow

Methods

runOp :: HideOverlay () -> orig -> Ref GlWindow -> impl Source #

impl ~ IO () => Op (Ortho ()) GlWindow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.GlWindow

Methods

runOp :: Ortho () -> orig -> Ref GlWindow -> impl Source #

impl ~ IO () => Op (SwapBuffers ()) GlWindow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.GlWindow

Methods

runOp :: SwapBuffers () -> orig -> Ref GlWindow -> impl Source #

impl ~ (Ref FlGlContext -> Bool -> IO ()) => Op (SetContextWithDestroyFlag ()) GlWindow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.GlWindow

Methods

runOp :: SetContextWithDestroyFlag () -> orig -> Ref GlWindow -> impl Source #

impl ~ (Ref FlGlContext -> IO ()) => Op (SetContext ()) GlWindow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.GlWindow

Methods

runOp :: SetContext () -> orig -> Ref GlWindow -> impl Source #

impl ~ IO (Ref FlGlContext) => Op (GetContext ()) GlWindow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.GlWindow

Methods

runOp :: GetContext () -> orig -> Ref GlWindow -> impl Source #

impl ~ IO Bool => Op (CanDo ()) GlWindow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.GlWindow

Methods

runOp :: CanDo () -> orig -> Ref GlWindow -> impl Source #

impl ~ (Bool -> IO ()) => Op (SetContextValid ()) GlWindow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.GlWindow

Methods

runOp :: SetContextValid () -> orig -> Ref GlWindow -> impl Source #

impl ~ IO Bool => Op (GetContextValid ()) GlWindow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.GlWindow

Methods

runOp :: GetContextValid () -> orig -> Ref GlWindow -> impl Source #

impl ~ IO () => Op (Invalidate ()) GlWindow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.GlWindow

Methods

runOp :: Invalidate () -> orig -> Ref GlWindow -> impl Source #

impl ~ (Bool -> IO ()) => Op (SetValid ()) GlWindow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.GlWindow

Methods

runOp :: SetValid () -> orig -> Ref GlWindow -> impl Source #

impl ~ IO Bool => Op (GetValid ()) GlWindow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.GlWindow

Methods

runOp :: GetValid () -> orig -> Ref GlWindow -> impl Source #

impl ~ (TableRowSelectFlag -> IO ()) => Op (SelectAllRows ()) TableRow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TableRow

Methods

runOp :: SelectAllRows () -> orig -> Ref TableRow -> impl Source #

impl ~ (Row -> IO (Either OutOfRange Bool)) => Op (GetRowSelected ()) TableRow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TableRow

Methods

runOp :: GetRowSelected () -> orig -> Ref TableRow -> impl Source #

impl ~ IO Bool => Op (GetTabCellNav ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: GetTabCellNav () -> orig -> Ref Table -> impl Source #

impl ~ (Bool -> IO ()) => Op (SetTabCellNav ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: SetTabCellNav () -> orig -> Ref Table -> impl Source #

impl ~ (Columns -> IO ()) => Op (SetColsSuper ()) TableRow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TableRow

Methods

runOp :: SetColsSuper () -> orig -> Ref TableRow -> impl Source #

impl ~ (Columns -> IO ()) => Op (SetColsSuper ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: SetColsSuper () -> orig -> Ref Table -> impl Source #

impl ~ (Rows -> IO ()) => Op (SetRowsSuper ()) TableRow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TableRow

Methods

runOp :: SetRowsSuper () -> orig -> Ref TableRow -> impl Source #

impl ~ (Rows -> IO ()) => Op (SetRowsSuper ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: SetRowsSuper () -> orig -> Ref Table -> impl Source #

impl ~ IO () => Op (ClearSuper ()) TableRow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TableRow

Methods

runOp :: ClearSuper () -> orig -> Ref TableRow -> impl Source #

impl ~ IO () => Op (ClearSuper ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: ClearSuper () -> orig -> Ref Table -> impl Source #

impl ~ (TableContext -> TableCoordinate -> IO (Maybe Rectangle)) => Op (FindCell ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: FindCell () -> orig -> Ref Table -> impl Source #

impl ~ IO TableContext => Op (CallbackContext ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: CallbackContext () -> orig -> Ref Table -> impl Source #

impl ~ IO Column => Op (CallbackCol ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: CallbackCol () -> orig -> Ref Table -> impl Source #

impl ~ IO Row => Op (CallbackRow ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: CallbackRow () -> orig -> Ref Table -> impl Source #

impl ~ (TableCoordinate -> IO (Either NoChange ())) => Op (MoveCursor ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: MoveCursor () -> orig -> Ref Table -> impl Source #

impl ~ (TableCoordinate -> TableCoordinate -> IO ()) => Op (SetSelection ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: SetSelection () -> orig -> Ref Table -> impl Source #

impl ~ IO (TableCoordinate, TableCoordinate) => Op (GetSelection ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: GetSelection () -> orig -> Ref Table -> impl Source #

impl ~ (TreeItemLocator -> IO Bool) => Op (IsSelected ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: IsSelected () -> orig -> Ref Tree -> impl Source #

impl ~ IO Bool => Op (IsSelected ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: IsSelected () -> orig -> Ref TreeItem -> impl Source #

impl ~ (TableCoordinate -> IO Bool) => Op (IsSelected ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: IsSelected () -> orig -> Ref Table -> impl Source #

impl ~ IO Row => Op (GetTopRow ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: GetTopRow () -> orig -> Ref Table -> impl Source #

impl ~ (Row -> IO ()) => Op (SetTopRow ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: SetTopRow () -> orig -> Ref Table -> impl Source #

impl ~ IO Column => Op (GetColPosition ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: GetColPosition () -> orig -> Ref Table -> impl Source #

impl ~ IO Row => Op (GetRowPosition ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: GetRowPosition () -> orig -> Ref Table -> impl Source #

impl ~ (Column -> IO ()) => Op (SetColPosition ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: SetColPosition () -> orig -> Ref Table -> impl Source #

impl ~ (Row -> IO ()) => Op (SetRowPosition ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: SetRowPosition () -> orig -> Ref Table -> impl Source #

impl ~ (Int -> IO ()) => Op (SetColWidthAll ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: SetColWidthAll () -> orig -> Ref Table -> impl Source #

impl ~ (Int -> IO ()) => Op (SetRowHeightAll ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: SetRowHeightAll () -> orig -> Ref Table -> impl Source #

impl ~ (Column -> IO Int) => Op (GetColWidth ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: GetColWidth () -> orig -> Ref Table -> impl Source #

impl ~ (Column -> Int -> IO ()) => Op (SetColWidth ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: SetColWidth () -> orig -> Ref Table -> impl Source #

impl ~ (Row -> IO Int) => Op (GetRowHeight ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: GetRowHeight () -> orig -> Ref Table -> impl Source #

impl ~ (Row -> Int -> IO ()) => Op (SetRowHeight ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: SetRowHeight () -> orig -> Ref Table -> impl Source #

impl ~ IO Color => Op (GetColHeaderColor ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: GetColHeaderColor () -> orig -> Ref Table -> impl Source #

impl ~ (Color -> IO ()) => Op (SetColHeaderColor ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: SetColHeaderColor () -> orig -> Ref Table -> impl Source #

impl ~ IO Color => Op (GetRowHeaderColor ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: GetRowHeaderColor () -> orig -> Ref Table -> impl Source #

impl ~ (Color -> IO ()) => Op (SetRowHeaderColor ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: SetRowHeaderColor () -> orig -> Ref Table -> impl Source #

impl ~ IO Int => Op (GetRowHeaderWidth ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: GetRowHeaderWidth () -> orig -> Ref Table -> impl Source #

impl ~ (Int -> IO ()) => Op (SetRowHeaderWidth ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: SetRowHeaderWidth () -> orig -> Ref Table -> impl Source #

impl ~ IO Int => Op (GetColHeaderHeight ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: GetColHeaderHeight () -> orig -> Ref Table -> impl Source #

impl ~ (Int -> IO ()) => Op (SetColHeaderHeight ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: SetColHeaderHeight () -> orig -> Ref Table -> impl Source #

impl ~ (Bool -> IO ()) => Op (SetColHeader ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: SetColHeader () -> orig -> Ref Table -> impl Source #

impl ~ IO Bool => Op (GetColHeader ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: GetColHeader () -> orig -> Ref Table -> impl Source #

impl ~ (Bool -> IO ()) => Op (SetRowHeader ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: SetRowHeader () -> orig -> Ref Table -> impl Source #

impl ~ IO Bool => Op (GetRowHeader ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: GetRowHeader () -> orig -> Ref Table -> impl Source #

impl ~ (Int -> IO ()) => Op (SetRowResizeMin ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: SetRowResizeMin () -> orig -> Ref Table -> impl Source #

impl ~ IO Int => Op (GetRowResizeMin ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: GetRowResizeMin () -> orig -> Ref Table -> impl Source #

impl ~ (Int -> IO ()) => Op (SetColResizeMin ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: SetColResizeMin () -> orig -> Ref Table -> impl Source #

impl ~ IO Int => Op (GetColResizeMin ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: GetColResizeMin () -> orig -> Ref Table -> impl Source #

impl ~ (Bool -> IO ()) => Op (SetColResize ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: SetColResize () -> orig -> Ref Table -> impl Source #

impl ~ IO Bool => Op (GetColResize ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: GetColResize () -> orig -> Ref Table -> impl Source #

impl ~ (Bool -> IO ()) => Op (SetRowResize ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: SetRowResize () -> orig -> Ref Table -> impl Source #

impl ~ IO Bool => Op (GetRowResize ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: GetRowResize () -> orig -> Ref Table -> impl Source #

impl ~ IO Bool => Op (IsInteractiveResize ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: IsInteractiveResize () -> orig -> Ref Table -> impl Source #

impl ~ IO (TableCoordinate, TableCoordinate) => Op (GetVisibleCells ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: GetVisibleCells () -> orig -> Ref Table -> impl Source #

impl ~ IO Columns => Op (GetCols ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: GetCols () -> orig -> Ref Table -> impl Source #

impl ~ (Columns -> IO ()) => Op (SetCols ()) TableRow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TableRow

Methods

runOp :: SetCols () -> orig -> Ref TableRow -> impl Source #

impl ~ (Columns -> IO ()) => Op (SetCols ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: SetCols () -> orig -> Ref Table -> impl Source #

impl ~ IO Rows => Op (GetRows ()) TableRow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TableRow

Methods

runOp :: GetRows () -> orig -> Ref TableRow -> impl Source #

impl ~ IO Rows => Op (GetRows ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: GetRows () -> orig -> Ref Table -> impl Source #

impl ~ (Rows -> IO ()) => Op (SetRows ()) TableRow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TableRow

Methods

runOp :: SetRows () -> orig -> Ref TableRow -> impl Source #

impl ~ (Rows -> IO ()) => Op (SetRows ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: SetRows () -> orig -> Ref Table -> impl Source #

impl ~ IO Boxtype => Op (GetTableBox ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: GetTableBox () -> orig -> Ref Table -> impl Source #

impl ~ (Boxtype -> IO ()) => Op (SetTableBox ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: SetTableBox () -> orig -> Ref Table -> impl Source #

impl ~ IO (Maybe (Ref TreeItem)) => Op (Prev ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: Prev () -> orig -> Ref Tree -> impl Source #

impl ~ IO (Maybe (Ref TreeItem)) => Op (Prev ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: Prev () -> orig -> Ref TreeItem -> impl Source #

impl ~ IO () => Op (Prev ()) Wizard orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Wizard

Methods

runOp :: Prev () -> orig -> Ref Wizard -> impl Source #

impl ~ (Double -> IO ()) => Op (SetYstep ()) Positioner orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Positioner

Methods

runOp :: SetYstep () -> orig -> Ref Positioner -> impl Source #

impl ~ (Double -> IO ()) => Op (SetXstep ()) Positioner orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Positioner

Methods

runOp :: SetXstep () -> orig -> Ref Positioner -> impl Source #

impl ~ (PreciseY -> PreciseY -> IO ()) => Op (SetYbounds ()) Positioner orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Positioner

Methods

runOp :: SetYbounds () -> orig -> Ref Positioner -> impl Source #

impl ~ (PreciseX -> PreciseX -> IO ()) => Op (SetXbounds ()) Positioner orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Positioner

Methods

runOp :: SetXbounds () -> orig -> Ref Positioner -> impl Source #

impl ~ IO PreciseY => Op (GetYmaximum ()) Positioner orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Positioner

Methods

runOp :: GetYmaximum () -> orig -> Ref Positioner -> impl Source #

impl ~ (PreciseY -> IO ()) => Op (SetYmaximum ()) Positioner orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Positioner

Methods

runOp :: SetYmaximum () -> orig -> Ref Positioner -> impl Source #

impl ~ IO PreciseX => Op (GetXmaximum ()) Positioner orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Positioner

Methods

runOp :: GetXmaximum () -> orig -> Ref Positioner -> impl Source #

impl ~ (PreciseX -> IO ()) => Op (SetXmaximum ()) Positioner orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Positioner

Methods

runOp :: SetXmaximum () -> orig -> Ref Positioner -> impl Source #

impl ~ IO PreciseY => Op (GetYminimum ()) Positioner orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Positioner

Methods

runOp :: GetYminimum () -> orig -> Ref Positioner -> impl Source #

impl ~ (PreciseY -> IO ()) => Op (SetYminimum ()) Positioner orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Positioner

Methods

runOp :: SetYminimum () -> orig -> Ref Positioner -> impl Source #

impl ~ IO PreciseX => Op (GetXminimum ()) Positioner orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Positioner

Methods

runOp :: GetXminimum () -> orig -> Ref Positioner -> impl Source #

impl ~ (PreciseX -> IO ()) => Op (SetXminimum ()) Positioner orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Positioner

Methods

runOp :: SetXminimum () -> orig -> Ref Positioner -> impl Source #

impl ~ IO PreciseY => Op (GetYvalue ()) Positioner orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Positioner

Methods

runOp :: GetYvalue () -> orig -> Ref Positioner -> impl Source #

impl ~ (PreciseY -> IO ()) => Op (SetYvalue ()) Positioner orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Positioner

Methods

runOp :: SetYvalue () -> orig -> Ref Positioner -> impl Source #

impl ~ IO PreciseX => Op (GetXvalue ()) Positioner orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Positioner

Methods

runOp :: GetXvalue () -> orig -> Ref Positioner -> impl Source #

impl ~ (PreciseX -> IO ()) => Op (SetXvalue ()) Positioner orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Positioner

Methods

runOp :: SetXvalue () -> orig -> Ref Positioner -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (DrawText ()) Input orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Input

Methods

runOp :: DrawText () -> orig -> Ref Input -> impl Source #

impl ~ (Bool -> IO ()) => Op (SetTabNav ()) Input orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Input

Methods

runOp :: SetTabNav () -> orig -> Ref Input -> impl Source #

impl ~ IO Bool => Op (GetTabNav ()) Input orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Input

Methods

runOp :: GetTabNav () -> orig -> Ref Input -> impl Source #

impl ~ (Bool -> IO ()) => Op (SetWrap ()) Spinner orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Spinner

Methods

runOp :: SetWrap () -> orig -> Ref Spinner -> impl Source #

impl ~ (Bool -> IO ()) => Op (SetWrap ()) Input orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Input

Methods

runOp :: SetWrap () -> orig -> Ref Input -> impl Source #

impl ~ IO Bool => Op (GetWrap ()) Spinner orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Spinner

Methods

runOp :: GetWrap () -> orig -> Ref Spinner -> impl Source #

impl ~ IO Bool => Op (GetWrap ()) Input orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Input

Methods

runOp :: GetWrap () -> orig -> Ref Input -> impl Source #

impl ~ (Bool -> IO ()) => Op (SetReadonly ()) Input orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Input

Methods

runOp :: SetReadonly () -> orig -> Ref Input -> impl Source #

impl ~ IO Bool => Op (GetReadonly ()) Input orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Input

Methods

runOp :: GetReadonly () -> orig -> Ref Input -> impl Source #

impl ~ (FlInputType -> IO ()) => Op (SetInputType ()) Input orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Input

Methods

runOp :: SetInputType () -> orig -> Ref Input -> impl Source #

impl ~ IO FlInputType => Op (GetInputType ()) Input orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Input

Methods

runOp :: GetInputType () -> orig -> Ref Input -> impl Source #

impl ~ (Color -> IO ()) => Op (SetCursorColor ()) TextDisplay orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextDisplay

Methods

runOp :: SetCursorColor () -> orig -> Ref TextDisplay -> impl Source #

impl ~ (Color -> IO ()) => Op (SetCursorColor ()) Input orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Input

Methods

runOp :: SetCursorColor () -> orig -> Ref Input -> impl Source #

impl ~ IO Color => Op (GetCursorColor ()) TextDisplay orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextDisplay

Methods

runOp :: GetCursorColor () -> orig -> Ref TextDisplay -> impl Source #

impl ~ IO Color => Op (GetCursorColor ()) Input orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Input

Methods

runOp :: GetCursorColor () -> orig -> Ref Input -> impl Source #

impl ~ IO (Either NoChange ()) => Op (CopyCuts ()) Input orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Input

Methods

runOp :: CopyCuts () -> orig -> Ref Input -> impl Source #

impl ~ IO (Either NoChange AtIndex) => Op (Undo ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: Undo () -> orig -> Ref TextBuffer -> impl Source #

impl ~ IO (Either NoChange ()) => Op (Undo ()) Input orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Input

Methods

runOp :: Undo () -> orig -> Ref Input -> impl Source #

impl ~ (Text -> Int -> IO (Either NoChange ())) => Op (InsertWithLength ()) Input orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Input

Methods

runOp :: InsertWithLength () -> orig -> Ref Input -> impl Source #

impl ~ (IndexRange -> IO (Either NoChange ())) => Op (CutRange ()) Input orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Input

Methods

runOp :: CutRange () -> orig -> Ref Input -> impl Source #

impl ~ (Int -> IO (Either NoChange ())) => Op (CutFromCursor ()) Input orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Input

Methods

runOp :: CutFromCursor () -> orig -> Ref Input -> impl Source #

impl ~ IO (Either NoChange ()) => Op (Cut ()) Input orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Input

Methods

runOp :: Cut () -> orig -> Ref Input -> impl Source #

impl ~ (Int -> IO (Either NoChange ())) => Op (SetMark ()) Input orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Input

Methods

runOp :: SetMark () -> orig -> Ref Input -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (SetPosition ()) Tile orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tile

Methods

runOp :: SetPosition () -> orig -> Ref Tile -> impl Source #

impl ~ (PixelPosition -> IO ()) => Op (SetPosition ()) Browser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Browser

Methods

runOp :: SetPosition () -> orig -> Ref Browser -> impl Source #

impl ~ (Int -> Maybe Int -> IO (Either NoChange ())) => Op (SetPosition ()) Input orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Input

Methods

runOp :: SetPosition () -> orig -> Ref Input -> impl Source #

impl ~ IO Int => Op (GetMark ()) Input orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Input

Methods

runOp :: GetMark () -> orig -> Ref Input -> impl Source #

impl ~ IO (Maybe IndexRange) => Op (GetPosition ()) TextSelection orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextSelection

Methods

runOp :: GetPosition () -> orig -> Ref TextSelection -> impl Source #

impl ~ IO PixelPosition => Op (GetPosition ()) Browser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Browser

Methods

runOp :: GetPosition () -> orig -> Ref Browser -> impl Source #

impl ~ IO Int => Op (GetPosition ()) Input orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Input

Methods

runOp :: GetPosition () -> orig -> Ref Input -> impl Source #

impl ~ (Int -> IO ()) => Op (SetMaximumSize ()) Input orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Input

Methods

runOp :: SetMaximumSize () -> orig -> Ref Input -> impl Source #

impl ~ IO Int => Op (GetMaximumSize ()) Input orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Input

Methods

runOp :: GetMaximumSize () -> orig -> Ref Input -> impl Source #

impl ~ (AtIndex -> IO Char) => Op (Index ()) Input orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Input

Methods

runOp :: Index () -> orig -> Ref Input -> impl Source #

impl ~ (Text -> IO (Either NoChange ())) => Op (StaticValue ()) Input orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Input

Methods

runOp :: StaticValue () -> orig -> Ref Input -> impl Source #

impl ~ IO LineSize => Op (GetLinesize ()) Scrollbar orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Scrollbar

Methods

runOp :: GetLinesize () -> orig -> Ref Scrollbar -> impl Source #

impl ~ (LineSize -> IO ()) => Op (SetLinesize ()) Scrollbar orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Scrollbar

Methods

runOp :: SetLinesize () -> orig -> Ref Scrollbar -> impl Source #

impl ~ (Double -> IO ()) => Op (SetLstep ()) Counter orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Counter

Methods

runOp :: SetLstep () -> orig -> Ref Counter -> impl Source #

impl ~ (Angle -> Angle -> IO ()) => Op (SetAngles ()) Dial orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Dial

Methods

runOp :: SetAngles () -> orig -> Ref Dial -> impl Source #

impl ~ (Angle -> IO ()) => Op (SetAngle2 ()) Dial orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Dial

Methods

runOp :: SetAngle2 () -> orig -> Ref Dial -> impl Source #

impl ~ IO Angle => Op (GetAngle2 ()) Dial orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Dial

Methods

runOp :: GetAngle2 () -> orig -> Ref Dial -> impl Source #

impl ~ (Angle -> IO ()) => Op (SetAngle1 ()) Dial orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Dial

Methods

runOp :: SetAngle1 () -> orig -> Ref Dial -> impl Source #

impl ~ IO Angle => Op (GetAngle1 ()) Dial orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Dial

Methods

runOp :: GetAngle1 () -> orig -> Ref Dial -> impl Source #

impl ~ IO Bool => Op (GetSoft ()) ValueOutput orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ValueOutput

Methods

runOp :: GetSoft () -> orig -> Ref ValueOutput -> impl Source #

impl ~ IO Bool => Op (GetSoft ()) ValueInput orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ValueInput

Methods

runOp :: GetSoft () -> orig -> Ref ValueInput -> impl Source #

impl ~ IO Bool => Op (GetSoft ()) Adjuster orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Adjuster

Methods

runOp :: GetSoft () -> orig -> Ref Adjuster -> impl Source #

impl ~ (Bool -> IO ()) => Op (SetSoft ()) ValueOutput orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ValueOutput

Methods

runOp :: SetSoft () -> orig -> Ref ValueOutput -> impl Source #

impl ~ (Bool -> IO ()) => Op (SetSoft ()) ValueInput orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ValueInput

Methods

runOp :: SetSoft () -> orig -> Ref ValueInput -> impl Source #

impl ~ (Bool -> IO ()) => Op (SetSoft ()) Adjuster orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Adjuster

Methods

runOp :: SetSoft () -> orig -> Ref Adjuster -> impl Source #

impl ~ IO FlOffscreen => Op (GetOffscreen ()) ImageSurface orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ImageSurface

Methods

runOp :: GetOffscreen () -> orig -> Ref ImageSurface -> impl Source #

impl ~ (Position -> IO ()) => Op (SetOrigin ()) ImageSurface orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ImageSurface

Methods

runOp :: SetOrigin () -> orig -> Ref ImageSurface -> impl Source #

impl ~ IO (Either UnknownError Size) => Op (PrintableRect ()) ImageSurface orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ImageSurface

Methods

runOp :: PrintableRect () -> orig -> Ref ImageSurface -> impl Source #

impl ~ IO Position => Op (GetOrigin ()) ImageSurface orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ImageSurface

Methods

runOp :: GetOrigin () -> orig -> Ref ImageSurface -> impl Source #

impl ~ IO () => Op (SetCurrent ()) ImageSurface orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ImageSurface

Methods

runOp :: SetCurrent () -> orig -> Ref ImageSurface -> impl Source #

impl ~ IO () => Op (SetCurrent ()) CopySurface orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.CopySurface

Methods

runOp :: SetCurrent () -> orig -> Ref CopySurface -> impl Source #

impl ~ IO Size => Op (GetDataSize ()) Image orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Image

Methods

runOp :: GetDataSize () -> orig -> Ref Image -> impl Source #

impl ~ IO Height => Op (GetDataH ()) Image orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Image

Methods

runOp :: GetDataH () -> orig -> Ref Image -> impl Source #

impl ~ IO Width => Op (GetDataW ()) Image orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Image

Methods

runOp :: GetDataW () -> orig -> Ref Image -> impl Source #

impl ~ (Size -> Maybe Bool -> Maybe Bool -> IO ()) => Op (Scale ()) Image orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Image

Methods

runOp :: Scale () -> orig -> Ref Image -> impl Source #

impl ~ IO (Either ImageFail ()) => Op (Fail ()) Image orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Image

Methods

runOp :: Fail () -> orig -> Ref Image -> impl Source #

impl ~ IO () => Op (Uncache ()) RGBImage orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.RGBImage

Methods

runOp :: Uncache () -> orig -> Ref RGBImage -> impl Source #

impl ~ IO () => Op (Uncache ()) Pixmap orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Pixmap

Methods

runOp :: Uncache () -> orig -> Ref Pixmap -> impl Source #

impl ~ IO () => Op (Uncache ()) Bitmap orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Bitmap

Methods

runOp :: Uncache () -> orig -> Ref Bitmap -> impl Source #

impl ~ IO () => Op (Uncache ()) Image orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Image

Methods

runOp :: Uncache () -> orig -> Ref Image -> impl Source #

impl ~ (Position -> Size -> Maybe X -> Maybe Y -> IO ()) => Op (DrawResize ()) SVGImage orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.SVGImage

Methods

runOp :: DrawResize () -> orig -> Ref SVGImage -> impl Source #

impl ~ (Position -> Size -> Maybe X -> Maybe Y -> IO ()) => Op (DrawResize ()) RGBImage orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.RGBImage

Methods

runOp :: DrawResize () -> orig -> Ref RGBImage -> impl Source #

impl ~ (Position -> Size -> Maybe X -> Maybe Y -> IO ()) => Op (DrawResize ()) Pixmap orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Pixmap

Methods

runOp :: DrawResize () -> orig -> Ref Pixmap -> impl Source #

impl ~ (Position -> Size -> Maybe X -> Maybe Y -> IO ()) => Op (DrawResize ()) Bitmap orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Bitmap

Methods

runOp :: DrawResize () -> orig -> Ref Bitmap -> impl Source #

impl ~ (Position -> Size -> Maybe X -> Maybe Y -> IO ()) => Op (DrawResize ()) Image orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Image

Methods

runOp :: DrawResize () -> orig -> Ref Image -> impl Source #

impl ~ IO () => Op (Desaturate ()) SVGImage orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.SVGImage

Methods

runOp :: Desaturate () -> orig -> Ref SVGImage -> impl Source #

impl ~ IO () => Op (Desaturate ()) RGBImage orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.RGBImage

Methods

runOp :: Desaturate () -> orig -> Ref RGBImage -> impl Source #

impl ~ IO () => Op (Desaturate ()) Pixmap orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Pixmap

Methods

runOp :: Desaturate () -> orig -> Ref Pixmap -> impl Source #

impl ~ IO () => Op (Desaturate ()) Bitmap orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Bitmap

Methods

runOp :: Desaturate () -> orig -> Ref Bitmap -> impl Source #

impl ~ IO () => Op (Desaturate ()) Image orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Image

Methods

runOp :: Desaturate () -> orig -> Ref Image -> impl Source #

impl ~ IO () => Op (Inactive ()) RGBImage orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.RGBImage

Methods

runOp :: Inactive () -> orig -> Ref RGBImage -> impl Source #

impl ~ IO () => Op (Inactive ()) Pixmap orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Pixmap

Methods

runOp :: Inactive () -> orig -> Ref Pixmap -> impl Source #

impl ~ IO () => Op (Inactive ()) Bitmap orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Bitmap

Methods

runOp :: Inactive () -> orig -> Ref Bitmap -> impl Source #

impl ~ IO () => Op (Inactive ()) Image orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Image

Methods

runOp :: Inactive () -> orig -> Ref Image -> impl Source #

impl ~ (Color -> Float -> IO ()) => Op (ColorAverage ()) SVGImage orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.SVGImage

Methods

runOp :: ColorAverage () -> orig -> Ref SVGImage -> impl Source #

impl ~ (Color -> Float -> IO ()) => Op (ColorAverage ()) RGBImage orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.RGBImage

Methods

runOp :: ColorAverage () -> orig -> Ref RGBImage -> impl Source #

impl ~ (Color -> Float -> IO ()) => Op (ColorAverage ()) Pixmap orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Pixmap

Methods

runOp :: ColorAverage () -> orig -> Ref Pixmap -> impl Source #

impl ~ (Color -> Float -> IO ()) => Op (ColorAverage ()) Bitmap orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Bitmap

Methods

runOp :: ColorAverage () -> orig -> Ref Bitmap -> impl Source #

impl ~ (Color -> Float -> IO ()) => Op (ColorAverage ()) Image orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Image

Methods

runOp :: ColorAverage () -> orig -> Ref Image -> impl Source #

impl ~ IO Int => Op (GetCount ()) RGBImage orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.RGBImage

Methods

runOp :: GetCount () -> orig -> Ref RGBImage -> impl Source #

impl ~ IO Int => Op (GetCount ()) NativeFileChooser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.NativeFileChooser

Methods

runOp :: GetCount () -> orig -> Ref NativeFileChooser -> impl Source #

impl ~ IO Int => Op (GetCount ()) Pixmap orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Pixmap

Methods

runOp :: GetCount () -> orig -> Ref Pixmap -> impl Source #

impl ~ IO Int => Op (GetCount ()) Bitmap orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Bitmap

Methods

runOp :: GetCount () -> orig -> Ref Bitmap -> impl Source #

impl ~ IO Int => Op (GetCount ()) Image orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Image

Methods

runOp :: GetCount () -> orig -> Ref Image -> impl Source #

impl ~ IO Int => Op (GetLd ()) RGBImage orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.RGBImage

Methods

runOp :: GetLd () -> orig -> Ref RGBImage -> impl Source #

impl ~ IO Int => Op (GetLd ()) Pixmap orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Pixmap

Methods

runOp :: GetLd () -> orig -> Ref Pixmap -> impl Source #

impl ~ IO Int => Op (GetLd ()) Bitmap orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Bitmap

Methods

runOp :: GetLd () -> orig -> Ref Bitmap -> impl Source #

impl ~ IO Int => Op (GetLd ()) Image orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Image

Methods

runOp :: GetLd () -> orig -> Ref Image -> impl Source #

impl ~ IO Int => Op (GetD ()) RGBImage orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.RGBImage

Methods

runOp :: GetD () -> orig -> Ref RGBImage -> impl Source #

impl ~ IO Int => Op (GetD ()) Pixmap orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Pixmap

Methods

runOp :: GetD () -> orig -> Ref Pixmap -> impl Source #

impl ~ IO Int => Op (GetD ()) Bitmap orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Bitmap

Methods

runOp :: GetD () -> orig -> Ref Bitmap -> impl Source #

impl ~ IO Int => Op (GetD ()) Image orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Image

Methods

runOp :: GetD () -> orig -> Ref Image -> impl Source #

(Parent a MenuItem, impl ~ (Text -> Maybe Shortcut -> Maybe (Ref a -> IO ()) -> MenuItemFlags -> IO (Ref MenuItem))) => Op (AddAndGetMenuItem ()) MenuPrim orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuPrim

Methods

runOp :: AddAndGetMenuItem () -> orig -> Ref MenuPrim -> impl Source #

impl ~ (Color -> IO ()) => Op (SetTextcolor ()) Spinner orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Spinner

Methods

runOp :: SetTextcolor () -> orig -> Ref Spinner -> impl Source #

impl ~ (Color -> IO ()) => Op (SetTextcolor ()) TextDisplay orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextDisplay

Methods

runOp :: SetTextcolor () -> orig -> Ref TextDisplay -> impl Source #

impl ~ (Color -> IO ()) => Op (SetTextcolor ()) Browser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Browser

Methods

runOp :: SetTextcolor () -> orig -> Ref Browser -> impl Source #

impl ~ (Color -> IO ()) => Op (SetTextcolor ()) ValueOutput orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ValueOutput

Methods

runOp :: SetTextcolor () -> orig -> Ref ValueOutput -> impl Source #

impl ~ (Color -> IO ()) => Op (SetTextcolor ()) ValueInput orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ValueInput

Methods

runOp :: SetTextcolor () -> orig -> Ref ValueInput -> impl Source #

impl ~ (Color -> IO ()) => Op (SetTextcolor ()) Input orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Input

Methods

runOp :: SetTextcolor () -> orig -> Ref Input -> impl Source #

impl ~ (Color -> IO ()) => Op (SetTextcolor ()) ValueSlider orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ValueSlider

Methods

runOp :: SetTextcolor () -> orig -> Ref ValueSlider -> impl Source #

impl ~ (Color -> IO ()) => Op (SetTextcolor ()) Counter orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Counter

Methods

runOp :: SetTextcolor () -> orig -> Ref Counter -> impl Source #

impl ~ (Color -> IO ()) => Op (SetTextcolor ()) MenuPrim orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuPrim

Methods

runOp :: SetTextcolor () -> orig -> Ref MenuPrim -> impl Source #

impl ~ IO Color => Op (GetTextcolor ()) Spinner orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Spinner

Methods

runOp :: GetTextcolor () -> orig -> Ref Spinner -> impl Source #

impl ~ IO Color => Op (GetTextcolor ()) TextDisplay orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextDisplay

Methods

runOp :: GetTextcolor () -> orig -> Ref TextDisplay -> impl Source #

impl ~ IO Color => Op (GetTextcolor ()) Browser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Browser

Methods

runOp :: GetTextcolor () -> orig -> Ref Browser -> impl Source #

impl ~ IO Color => Op (GetTextcolor ()) ValueOutput orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ValueOutput

Methods

runOp :: GetTextcolor () -> orig -> Ref ValueOutput -> impl Source #

impl ~ IO Color => Op (GetTextcolor ()) ValueInput orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ValueInput

Methods

runOp :: GetTextcolor () -> orig -> Ref ValueInput -> impl Source #

impl ~ IO Color => Op (GetTextcolor ()) Input orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Input

Methods

runOp :: GetTextcolor () -> orig -> Ref Input -> impl Source #

impl ~ IO Color => Op (GetTextcolor ()) ValueSlider orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ValueSlider

Methods

runOp :: GetTextcolor () -> orig -> Ref ValueSlider -> impl Source #

impl ~ IO Color => Op (GetTextcolor ()) Counter orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Counter

Methods

runOp :: GetTextcolor () -> orig -> Ref Counter -> impl Source #

impl ~ IO Color => Op (GetTextcolor ()) MenuPrim orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuPrim

Methods

runOp :: GetTextcolor () -> orig -> Ref MenuPrim -> impl Source #

impl ~ (FontSize -> IO ()) => Op (SetTextsize ()) FileBrowser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.FileBrowser

Methods

runOp :: SetTextsize () -> orig -> Ref FileBrowser -> impl Source #

impl ~ (FontSize -> IO ()) => Op (SetTextsize ()) Spinner orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Spinner

Methods

runOp :: SetTextsize () -> orig -> Ref Spinner -> impl Source #

impl ~ (FontSize -> IO ()) => Op (SetTextsize ()) TextDisplay orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextDisplay

Methods

runOp :: SetTextsize () -> orig -> Ref TextDisplay -> impl Source #

impl ~ (FontSize -> IO ()) => Op (SetTextsize ()) Browser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Browser

Methods

runOp :: SetTextsize () -> orig -> Ref Browser -> impl Source #

impl ~ (FontSize -> IO ()) => Op (SetTextsize ()) ValueOutput orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ValueOutput

Methods

runOp :: SetTextsize () -> orig -> Ref ValueOutput -> impl Source #

impl ~ (FontSize -> IO ()) => Op (SetTextsize ()) ValueInput orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ValueInput

Methods

runOp :: SetTextsize () -> orig -> Ref ValueInput -> impl Source #

impl ~ (FontSize -> IO ()) => Op (SetTextsize ()) Input orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Input

Methods

runOp :: SetTextsize () -> orig -> Ref Input -> impl Source #

impl ~ (FontSize -> IO ()) => Op (SetTextsize ()) ValueSlider orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ValueSlider

Methods

runOp :: SetTextsize () -> orig -> Ref ValueSlider -> impl Source #

impl ~ (FontSize -> IO ()) => Op (SetTextsize ()) Counter orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Counter

Methods

runOp :: SetTextsize () -> orig -> Ref Counter -> impl Source #

impl ~ (FontSize -> IO ()) => Op (SetTextsize ()) MenuPrim orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuPrim

Methods

runOp :: SetTextsize () -> orig -> Ref MenuPrim -> impl Source #

impl ~ IO FontSize => Op (GetTextsize ()) FileBrowser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.FileBrowser

Methods

runOp :: GetTextsize () -> orig -> Ref FileBrowser -> impl Source #

impl ~ IO FontSize => Op (GetTextsize ()) Spinner orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Spinner

Methods

runOp :: GetTextsize () -> orig -> Ref Spinner -> impl Source #

impl ~ IO FontSize => Op (GetTextsize ()) TextDisplay orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextDisplay

Methods

runOp :: GetTextsize () -> orig -> Ref TextDisplay -> impl Source #

impl ~ IO FontSize => Op (GetTextsize ()) Browser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Browser

Methods

runOp :: GetTextsize () -> orig -> Ref Browser -> impl Source #

impl ~ IO FontSize => Op (GetTextsize ()) ValueOutput orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ValueOutput

Methods

runOp :: GetTextsize () -> orig -> Ref ValueOutput -> impl Source #

impl ~ IO FontSize => Op (GetTextsize ()) ValueInput orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ValueInput

Methods

runOp :: GetTextsize () -> orig -> Ref ValueInput -> impl Source #

impl ~ IO FontSize => Op (GetTextsize ()) Input orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Input

Methods

runOp :: GetTextsize () -> orig -> Ref Input -> impl Source #

impl ~ IO FontSize => Op (GetTextsize ()) ValueSlider orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ValueSlider

Methods

runOp :: GetTextsize () -> orig -> Ref ValueSlider -> impl Source #

impl ~ IO FontSize => Op (GetTextsize ()) Counter orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Counter

Methods

runOp :: GetTextsize () -> orig -> Ref Counter -> impl Source #

impl ~ IO FontSize => Op (GetTextsize ()) MenuPrim orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuPrim

Methods

runOp :: GetTextsize () -> orig -> Ref MenuPrim -> impl Source #

impl ~ (Font -> IO ()) => Op (SetTextfont ()) Spinner orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Spinner

Methods

runOp :: SetTextfont () -> orig -> Ref Spinner -> impl Source #

impl ~ (Font -> IO ()) => Op (SetTextfont ()) TextDisplay orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextDisplay

Methods

runOp :: SetTextfont () -> orig -> Ref TextDisplay -> impl Source #

impl ~ (Font -> IO ()) => Op (SetTextfont ()) Browser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Browser

Methods

runOp :: SetTextfont () -> orig -> Ref Browser -> impl Source #

impl ~ (Font -> IO ()) => Op (SetTextfont ()) ValueOutput orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ValueOutput

Methods

runOp :: SetTextfont () -> orig -> Ref ValueOutput -> impl Source #

impl ~ (Font -> IO ()) => Op (SetTextfont ()) ValueInput orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ValueInput

Methods

runOp :: SetTextfont () -> orig -> Ref ValueInput -> impl Source #

impl ~ (Font -> IO ()) => Op (SetTextfont ()) Input orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Input

Methods

runOp :: SetTextfont () -> orig -> Ref Input -> impl Source #

impl ~ (Font -> IO ()) => Op (SetTextfont ()) ValueSlider orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ValueSlider

Methods

runOp :: SetTextfont () -> orig -> Ref ValueSlider -> impl Source #

impl ~ (Font -> IO ()) => Op (SetTextfont ()) Counter orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Counter

Methods

runOp :: SetTextfont () -> orig -> Ref Counter -> impl Source #

impl ~ (Font -> IO ()) => Op (SetTextfont ()) MenuPrim orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuPrim

Methods

runOp :: SetTextfont () -> orig -> Ref MenuPrim -> impl Source #

impl ~ IO Font => Op (GetTextfont ()) Spinner orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Spinner

Methods

runOp :: GetTextfont () -> orig -> Ref Spinner -> impl Source #

impl ~ IO Font => Op (GetTextfont ()) TextDisplay orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextDisplay

Methods

runOp :: GetTextfont () -> orig -> Ref TextDisplay -> impl Source #

impl ~ IO Font => Op (GetTextfont ()) Browser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Browser

Methods

runOp :: GetTextfont () -> orig -> Ref Browser -> impl Source #

impl ~ IO Font => Op (GetTextfont ()) ValueOutput orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ValueOutput

Methods

runOp :: GetTextfont () -> orig -> Ref ValueOutput -> impl Source #

impl ~ IO Font => Op (GetTextfont ()) ValueInput orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ValueInput

Methods

runOp :: GetTextfont () -> orig -> Ref ValueInput -> impl Source #

impl ~ IO Font => Op (GetTextfont ()) Input orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Input

Methods

runOp :: GetTextfont () -> orig -> Ref Input -> impl Source #

impl ~ IO Font => Op (GetTextfont ()) ValueSlider orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ValueSlider

Methods

runOp :: GetTextfont () -> orig -> Ref ValueSlider -> impl Source #

impl ~ IO Font => Op (GetTextfont ()) Counter orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Counter

Methods

runOp :: GetTextfont () -> orig -> Ref Counter -> impl Source #

impl ~ IO Font => Op (GetTextfont ()) MenuPrim orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuPrim

Methods

runOp :: GetTextfont () -> orig -> Ref MenuPrim -> impl Source #

impl ~ (AtIndex -> IO Text) => Op (GetTextWithIndex ()) MenuPrim orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuPrim

Methods

runOp :: GetTextWithIndex () -> orig -> Ref MenuPrim -> impl Source #

impl ~ IO Text => Op (GetText ()) SimpleTerminal orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.SimpleTerminal

Methods

runOp :: GetText () -> orig -> Ref SimpleTerminal -> impl Source #

impl ~ IO Text => Op (GetText ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: GetText () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (LineNumber -> IO Text) => Op (GetText ()) Browser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Browser

Methods

runOp :: GetText () -> orig -> Ref Browser -> impl Source #

impl ~ IO Text => Op (GetText ()) MenuPrim orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuPrim

Methods

runOp :: GetText () -> orig -> Ref MenuPrim -> impl Source #

impl ~ IO Text => Op (GetText ()) MenuItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuItem

Methods

runOp :: GetText () -> orig -> Ref MenuItem -> impl Source #

impl ~ IO (Maybe (Ref MenuItem)) => Op (Mvalue ()) MenuPrim orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuPrim

Methods

runOp :: Mvalue () -> orig -> Ref MenuPrim -> impl Source #

impl ~ IO ColorChooserMode => Op (GetMode ()) ColorChooser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ColorChooser

Methods

runOp :: GetMode () -> orig -> Ref ColorChooser -> impl Source #

impl ~ IO Mode => Op (GetMode ()) GlWindow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.GlWindow

Methods

runOp :: GetMode () -> orig -> Ref GlWindow -> impl Source #

impl ~ (AtIndex -> IO (Maybe MenuItemFlags)) => Op (GetMode ()) SysMenuBar orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.SysMenuBar

Methods

runOp :: GetMode () -> orig -> Ref SysMenuBar -> impl Source #

impl ~ (AtIndex -> IO (Maybe MenuItemFlags)) => Op (GetMode ()) MenuPrim orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuPrim

Methods

runOp :: GetMode () -> orig -> Ref MenuPrim -> impl Source #

impl ~ (ColorChooserMode -> IO ()) => Op (SetMode ()) ColorChooser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ColorChooser

Methods

runOp :: SetMode () -> orig -> Ref ColorChooser -> impl Source #

impl ~ (Modes -> IO ()) => Op (SetMode ()) GlWindow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.GlWindow

Methods

runOp :: SetMode () -> orig -> Ref GlWindow -> impl Source #

impl ~ (AtIndex -> MenuItemFlags -> IO ()) => Op (SetMode ()) SysMenuBar orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.SysMenuBar

Methods

runOp :: SetMode () -> orig -> Ref SysMenuBar -> impl Source #

impl ~ (AtIndex -> MenuItemFlags -> IO ()) => Op (SetMode ()) MenuPrim orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuPrim

Methods

runOp :: SetMode () -> orig -> Ref MenuPrim -> impl Source #

impl ~ (IndexRange -> IO ()) => Op (Remove ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: Remove () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (Ref TreeItem -> IO (Either TreeItemNotFound ())) => Op (Remove ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: Remove () -> orig -> Ref Tree -> impl Source #

impl ~ (LineNumber -> IO ()) => Op (Remove ()) Browser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Browser

Methods

runOp :: Remove () -> orig -> Ref Browser -> impl Source #

impl ~ (Int -> IO ()) => Op (Remove ()) SysMenuBar orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.SysMenuBar

Methods

runOp :: Remove () -> orig -> Ref SysMenuBar -> impl Source #

impl ~ (AtIndex -> IO ()) => Op (Remove ()) MenuPrim orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuPrim

Methods

runOp :: Remove () -> orig -> Ref MenuPrim -> impl Source #

impl ~ (IndexRange -> Text -> IO ()) => Op (Replace ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: Replace () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (IndexRange -> Text -> IO (Either NoChange ())) => Op (Replace ()) Input orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Input

Methods

runOp :: Replace () -> orig -> Ref Input -> impl Source #

impl ~ (AtIndex -> Text -> IO ()) => Op (Replace ()) SysMenuBar orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.SysMenuBar

Methods

runOp :: Replace () -> orig -> Ref SysMenuBar -> impl Source #

impl ~ (AtIndex -> Text -> IO ()) => Op (Replace ()) MenuPrim orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuPrim

Methods

runOp :: Replace () -> orig -> Ref MenuPrim -> impl Source #

impl ~ (Text -> IO ()) => Op (AddName ()) SysMenuBar orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.SysMenuBar

Methods

runOp :: AddName () -> orig -> Ref SysMenuBar -> impl Source #

impl ~ (Text -> IO ()) => Op (AddName ()) MenuPrim orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuPrim

Methods

runOp :: AddName () -> orig -> Ref MenuPrim -> impl Source #

impl ~ (AtIndex -> IO (Either OutOfRangeOrNotSubmenu ())) => Op (ClearSubmenu ()) SysMenuBar orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.SysMenuBar

Methods

runOp :: ClearSubmenu () -> orig -> Ref SysMenuBar -> impl Source #

impl ~ (AtIndex -> IO (Either OutOfRange ())) => Op (ClearSubmenu ()) MenuPrim orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuPrim

Methods

runOp :: ClearSubmenu () -> orig -> Ref MenuPrim -> impl Source #

impl ~ (Size -> IO ()) => Op (SetSize ()) Browser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Browser

Methods

runOp :: SetSize () -> orig -> Ref Browser -> impl Source #

impl ~ (Size -> IO ()) => Op (SetSize ()) Input orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Input

Methods

runOp :: SetSize () -> orig -> Ref Input -> impl Source #

impl ~ (Size -> IO ()) => Op (SetSize ()) MenuPrim orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuPrim

Methods

runOp :: SetSize () -> orig -> Ref MenuPrim -> impl Source #

impl ~ (Size -> IO (Maybe (Ref SVGImage))) => Op (Copy ()) SVGImage orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.SVGImage

Methods

runOp :: Copy () -> orig -> Ref SVGImage -> impl Source #

impl ~ (Maybe Size -> IO (Maybe (Ref orig))) => Op (Copy ()) RGBImage orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.RGBImage

Methods

runOp :: Copy () -> orig -> Ref RGBImage -> impl Source #

(Parent a TextBuffer, impl ~ (Ref a -> IndexRange -> AtIndex -> IO ())) => Op (Copy ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: Copy () -> orig -> Ref TextBuffer -> impl Source #

impl ~ (Clipboard -> IO (Either NoChange ())) => Op (Copy ()) Input orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Input

Methods

runOp :: Copy () -> orig -> Ref Input -> impl Source #

impl ~ (Maybe Size -> IO (Maybe (Ref Pixmap))) => Op (Copy ()) Pixmap orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Pixmap

Methods

runOp :: Copy () -> orig -> Ref Pixmap -> impl Source #

impl ~ (Maybe Size -> IO (Maybe (Ref Bitmap))) => Op (Copy ()) Bitmap orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Bitmap

Methods

runOp :: Copy () -> orig -> Ref Bitmap -> impl Source #

impl ~ (Maybe Size -> IO (Maybe (Ref Image))) => Op (Copy ()) Image orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Image

Methods

runOp :: Copy () -> orig -> Ref Image -> impl Source #

(Parent a MenuItem, impl ~ (Ref a -> IO ())) => Op (Copy ()) MenuPrim orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuPrim

Methods

runOp :: Copy () -> orig -> Ref MenuPrim -> impl Source #

impl ~ ([Ref MenuItem] -> IO ()) => Op (SetMenu ()) SysMenuBar orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.SysMenuBar

Methods

runOp :: SetMenu () -> orig -> Ref SysMenuBar -> impl Source #

(Parent a MenuItem, impl ~ ([Ref a] -> IO ())) => Op (SetMenu ()) MenuPrim orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuPrim

Methods

runOp :: SetMenu () -> orig -> Ref MenuPrim -> impl Source #

impl ~ IO [Maybe (Ref MenuItem)] => Op (GetMenu ()) MenuPrim orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuPrim

Methods

runOp :: GetMenu () -> orig -> Ref MenuPrim -> impl Source #

impl ~ IO () => Op (Global ()) SysMenuBar orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.SysMenuBar

Methods

runOp :: Global () -> orig -> Ref SysMenuBar -> impl Source #

impl ~ IO () => Op (Global ()) MenuPrim orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuPrim

Methods

runOp :: Global () -> orig -> Ref MenuPrim -> impl Source #

impl ~ (MenuItemLocator -> IO (Maybe Int)) => Op (FindIndex ()) MenuPrim orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuPrim

Methods

runOp :: FindIndex () -> orig -> Ref MenuPrim -> impl Source #

(Parent a MenuItem, Parent b MenuItem, impl ~ (Ref a -> IO (Maybe (Ref b)))) => Op (Picked ()) MenuPrim orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuPrim

Methods

runOp :: Picked () -> orig -> Ref MenuPrim -> impl Source #

impl ~ IO (Maybe String) => Op (ItemPathnameRecent ()) MenuPrim orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuPrim

Methods

runOp :: ItemPathnameRecent () -> orig -> Ref MenuPrim -> impl Source #

(Parent a TreeItem, impl ~ (Ref a -> IO (Maybe Text))) => Op (ItemPathname ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: ItemPathname () -> orig -> Ref Tree -> impl Source #

(Parent a MenuItem, impl ~ (Ref a -> IO (Maybe Text))) => Op (ItemPathname ()) MenuPrim orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuPrim

Methods

runOp :: ItemPathname () -> orig -> Ref MenuPrim -> impl Source #

impl ~ IO Int => Op (GetSize ()) Browser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Browser

Methods

runOp :: GetSize () -> orig -> Ref Browser -> impl Source #

impl ~ IO Int => Op (GetSize ()) Input orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Input

Methods

runOp :: GetSize () -> orig -> Ref Input -> impl Source #

impl ~ IO Int => Op (GetSize ()) MenuPrim orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuPrim

Methods

runOp :: GetSize () -> orig -> Ref MenuPrim -> impl Source #

impl ~ IO Int => Op (GetSize ()) MenuItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuItem

Methods

runOp :: GetSize () -> orig -> Ref MenuItem -> impl Source #

impl ~ (TableContext -> TableCoordinate -> IO ()) => Op (DoCallback ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: DoCallback () -> orig -> Ref Table -> impl Source #

impl ~ (Ref Widget -> IO ()) => Op (DoCallback ()) MenuItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuItem

Methods

runOp :: DoCallback () -> orig -> Ref MenuItem -> impl Source #

impl ~ IO () => Op (DoCallback ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: DoCallback () -> orig -> Ref Widget -> impl Source #

(Parent a MenuItem, impl ~ (Maybe AtIndex -> Bool -> IO (Maybe (Ref a)))) => Op (FindShortcut ()) MenuItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuItem

Methods

runOp :: FindShortcut () -> orig -> Ref MenuItem -> impl Source #

(Parent a MenuItem, impl ~ IO (Maybe (Ref a))) => Op (TestShortcut ()) MenuPrim orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuPrim

Methods

runOp :: TestShortcut () -> orig -> Ref MenuPrim -> impl Source #

(Parent a MenuItem, impl ~ IO (Maybe (Ref a))) => Op (TestShortcut ()) MenuItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuItem

Methods

runOp :: TestShortcut () -> orig -> Ref MenuItem -> impl Source #

impl ~ IO (Maybe (Ref MenuItem)) => Op (Popup ()) MenuButton orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuButton

Methods

runOp :: Popup () -> orig -> Ref MenuButton -> impl Source #

(Parent a MenuItem, Parent b MenuPrim, Parent c MenuItem, impl ~ (Position -> Maybe Text -> Maybe (Ref a) -> Maybe (Ref b) -> IO (Maybe (Ref c)))) => Op (Popup ()) MenuItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuItem

Methods

runOp :: Popup () -> orig -> Ref MenuItem -> impl Source #

(Parent a MenuPrim, Parent b MenuItem, Parent c MenuItem, impl ~ (Rectangle -> Maybe (Ref a) -> Maybe (Ref b) -> Maybe (Ref c) -> Maybe Bool -> IO (Maybe (Ref MenuItem)))) => Op (Pulldown ()) MenuItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuItem

Methods

runOp :: Pulldown () -> orig -> Ref MenuItem -> impl Source #

impl ~ (MenuItemFlags -> IO ()) => Op (SetFlags ()) MenuItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuItem

Methods

runOp :: SetFlags () -> orig -> Ref MenuItem -> impl Source #

impl ~ IO (Maybe MenuItemFlags) => Op (GetFlags ()) MenuItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuItem

Methods

runOp :: GetFlags () -> orig -> Ref MenuItem -> impl Source #

impl ~ (Position -> IO ()) => Op (Draw ()) SVGImage orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.SVGImage

Methods

runOp :: Draw () -> orig -> Ref SVGImage -> impl Source #

impl ~ IO () => Op (Draw ()) FileInput orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.FileInput

Methods

runOp :: Draw () -> orig -> Ref FileInput -> impl Source #

impl ~ (Position -> IO ()) => Op (Draw ()) RGBImage orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.RGBImage

Methods

runOp :: Draw () -> orig -> Ref RGBImage -> impl Source #

impl ~ IO () => Op (Draw ()) FileBrowser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.FileBrowser

Methods

runOp :: Draw () -> orig -> Ref FileBrowser -> impl Source #

impl ~ IO () => Op (Draw ()) ColorChooser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ColorChooser

Methods

runOp :: Draw () -> orig -> Ref ColorChooser -> impl Source #

impl ~ IO () => Op (Draw ()) Spinner orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Spinner

Methods

runOp :: Draw () -> orig -> Ref Spinner -> impl Source #

impl ~ IO () => Op (Draw ()) Tabs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tabs

Methods

runOp :: Draw () -> orig -> Ref Tabs -> impl Source #

impl ~ IO () => Op (Draw ()) Scrolled orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Scrolled

Methods

runOp :: Draw () -> orig -> Ref Scrolled -> impl Source #

impl ~ IO () => Op (Draw ()) Pack orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Pack

Methods

runOp :: Draw () -> orig -> Ref Pack -> impl Source #

impl ~ IO () => Op (Draw ()) Tile orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tile

Methods

runOp :: Draw () -> orig -> Ref Tile -> impl Source #

impl ~ IO () => Op (Draw ()) TextEditor orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextEditor

Methods

runOp :: Draw () -> orig -> Ref TextEditor -> impl Source #

impl ~ IO () => Op (Draw ()) TextDisplay orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextDisplay

Methods

runOp :: Draw () -> orig -> Ref TextDisplay -> impl Source #

impl ~ IO () => Op (Draw ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: Draw () -> orig -> Ref Tree -> impl Source #

impl ~ IO () => Op (Draw ()) Clock orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Clock

Methods

runOp :: Draw () -> orig -> Ref Clock -> impl Source #

impl ~ IO () => Op (Draw ()) TableRow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TableRow

Methods

runOp :: Draw () -> orig -> Ref TableRow -> impl Source #

impl ~ IO () => Op (Draw ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: Draw () -> orig -> Ref Table -> impl Source #

impl ~ IO () => Op (Draw ()) Wizard orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Wizard

Methods

runOp :: Draw () -> orig -> Ref Wizard -> impl Source #

impl ~ IO () => Op (Draw ()) Positioner orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Positioner

Methods

runOp :: Draw () -> orig -> Ref Positioner -> impl Source #

impl ~ IO () => Op (Draw ()) Progress orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Progress

Methods

runOp :: Draw () -> orig -> Ref Progress -> impl Source #

impl ~ IO () => Op (Draw ()) ValueOutput orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ValueOutput

Methods

runOp :: Draw () -> orig -> Ref ValueOutput -> impl Source #

impl ~ IO () => Op (Draw ()) ValueInput orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ValueInput

Methods

runOp :: Draw () -> orig -> Ref ValueInput -> impl Source #

impl ~ IO () => Op (Draw ()) Output orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Output

Methods

runOp :: Draw () -> orig -> Ref Output -> impl Source #

impl ~ IO () => Op (Draw ()) Input orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Input

Methods

runOp :: Draw () -> orig -> Ref Input -> impl Source #

impl ~ IO () => Op (Draw ()) ValueSlider orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ValueSlider

Methods

runOp :: Draw () -> orig -> Ref ValueSlider -> impl Source #

impl ~ IO () => Op (Draw ()) Scrollbar orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Scrollbar

Methods

runOp :: Draw () -> orig -> Ref Scrollbar -> impl Source #

impl ~ IO () => Op (Draw ()) Counter orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Counter

Methods

runOp :: Draw () -> orig -> Ref Counter -> impl Source #

impl ~ IO () => Op (Draw ()) Roller orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Roller

Methods

runOp :: Draw () -> orig -> Ref Roller -> impl Source #

impl ~ IO () => Op (Draw ()) Dial orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Dial

Methods

runOp :: Draw () -> orig -> Ref Dial -> impl Source #

impl ~ IO () => Op (Draw ()) Adjuster orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Adjuster

Methods

runOp :: Draw () -> orig -> Ref Adjuster -> impl Source #

(Parent a Widget, impl ~ (Ref a -> Position -> IO ())) => Op (Draw ()) ImageSurface orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ImageSurface

Methods

runOp :: Draw () -> orig -> Ref ImageSurface -> impl Source #

(Parent a Widget, impl ~ (Ref a -> Position -> IO ())) => Op (Draw ()) CopySurface orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.CopySurface

Methods

runOp :: Draw () -> orig -> Ref CopySurface -> impl Source #

impl ~ (Position -> IO ()) => Op (Draw ()) Pixmap orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Pixmap

Methods

runOp :: Draw () -> orig -> Ref Pixmap -> impl Source #

impl ~ (Position -> IO ()) => Op (Draw ()) Bitmap orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Bitmap

Methods

runOp :: Draw () -> orig -> Ref Bitmap -> impl Source #

impl ~ (Position -> IO ()) => Op (Draw ()) Image orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Image

Methods

runOp :: Draw () -> orig -> Ref Image -> impl Source #

impl ~ IO () => Op (Draw ()) MenuButton orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuButton

Methods

runOp :: Draw () -> orig -> Ref MenuButton -> impl Source #

impl ~ IO () => Op (Draw ()) Choice orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Choice

Methods

runOp :: Draw () -> orig -> Ref Choice -> impl Source #

impl ~ IO () => Op (Draw ()) SysMenuBar orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.SysMenuBar

Methods

runOp :: Draw () -> orig -> Ref SysMenuBar -> impl Source #

impl ~ IO () => Op (Draw ()) MenuBar orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuBar

Methods

runOp :: Draw () -> orig -> Ref MenuBar -> impl Source #

(Parent a MenuPrim, impl ~ (Rectangle -> Ref a -> IO ())) => Op (Draw ()) MenuItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuItem

Methods

runOp :: Draw () -> orig -> Ref MenuItem -> impl Source #

impl ~ IO () => Op (Draw ()) Slider orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Slider

Methods

runOp :: Draw () -> orig -> Ref Slider -> impl Source #

impl ~ IO () => Op (Draw ()) RepeatButton orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.RepeatButton

Methods

runOp :: Draw () -> orig -> Ref RepeatButton -> impl Source #

impl ~ IO () => Op (Draw ()) RoundButton orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.RoundButton

Methods

runOp :: Draw () -> orig -> Ref RoundButton -> impl Source #

impl ~ IO () => Op (Draw ()) ReturnButton orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ReturnButton

Methods

runOp :: Draw () -> orig -> Ref ReturnButton -> impl Source #

impl ~ IO () => Op (Draw ()) CheckButton orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.CheckButton

Methods

runOp :: Draw () -> orig -> Ref CheckButton -> impl Source #

impl ~ IO () => Op (Draw ()) LightButton orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.LightButton

Methods

runOp :: Draw () -> orig -> Ref LightButton -> impl Source #

(Parent a MenuPrim, impl ~ (Rectangle -> Ref a -> Bool -> IO ())) => Op (DrawWithT ()) MenuItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuItem

Methods

runOp :: DrawWithT () -> orig -> Ref MenuItem -> impl Source #

(Parent a MenuPrim, impl ~ (Ref a -> IO Size)) => Op (Measure ()) MenuItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuItem

Methods

runOp :: Measure () -> orig -> Ref MenuItem -> impl Source #

impl ~ IO Bool => Op (Activevisible ()) MenuItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuItem

Methods

runOp :: Activevisible () -> orig -> Ref MenuItem -> impl Source #

impl ~ IO Bool => Op (Visible ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: Visible () -> orig -> Ref TreeItem -> impl Source #

impl ~ (LineNumber -> IO Bool) => Op (Visible ()) Browser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Browser

Methods

runOp :: Visible () -> orig -> Ref Browser -> impl Source #

impl ~ IO Bool => Op (Visible ()) MenuItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuItem

Methods

runOp :: Visible () -> orig -> Ref MenuItem -> impl Source #

impl ~ IO Bool => Op (Radio ()) MenuItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuItem

Methods

runOp :: Radio () -> orig -> Ref MenuItem -> impl Source #

impl ~ IO Bool => Op (Checkbox ()) MenuItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuItem

Methods

runOp :: Checkbox () -> orig -> Ref MenuItem -> impl Source #

impl ~ IO Bool => Op (Submenu ()) MenuItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuItem

Methods

runOp :: Submenu () -> orig -> Ref MenuItem -> impl Source #

impl ~ (Labeltype -> Text -> IO ()) => Op (SetLabelWithLabeltype ()) MenuItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuItem

Methods

runOp :: SetLabelWithLabeltype () -> orig -> Ref MenuItem -> impl Source #

impl ~ IO (Maybe (Ref TreeItem)) => Op (GetFirst ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: GetFirst () -> orig -> Ref Tree -> impl Source #

impl ~ IO (Maybe (Ref MenuItem)) => Op (GetFirst ()) MenuItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuItem

Methods

runOp :: GetFirst () -> orig -> Ref MenuItem -> impl Source #

impl ~ IO (Maybe (Ref TreeItem)) => Op (Next ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: Next () -> orig -> Ref Tree -> impl Source #

impl ~ IO (Maybe (Ref TreeItem)) => Op (Next ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: Next () -> orig -> Ref TreeItem -> impl Source #

impl ~ IO () => Op (Next ()) Wizard orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Wizard

Methods

runOp :: Next () -> orig -> Ref Wizard -> impl Source #

impl ~ IO (Maybe (Ref MenuItem)) => Op (Next ()) MenuItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuItem

Methods

runOp :: Next () -> orig -> Ref MenuItem -> impl Source #

(Parent a MenuItem, impl ~ (Int -> IO (Maybe (Ref a)))) => Op (NextWithStep ()) MenuItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuItem

Methods

runOp :: NextWithStep () -> orig -> Ref MenuItem -> impl Source #

impl ~ (Boxtype -> IO ()) => Op (SetSlider ()) Slider orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Slider

Methods

runOp :: SetSlider () -> orig -> Ref Slider -> impl Source #

impl ~ IO Boxtype => Op (GetSlider ()) Slider orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Slider

Methods

runOp :: GetSlider () -> orig -> Ref Slider -> impl Source #

impl ~ IO Double => Op (GetSliderSize ()) Slider orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Slider

Methods

runOp :: GetSliderSize () -> orig -> Ref Slider -> impl Source #

impl ~ (Double -> IO ()) => Op (SetSliderSize ()) Slider orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Slider

Methods

runOp :: SetSliderSize () -> orig -> Ref Slider -> impl Source #

impl ~ (Y -> Lines -> LineNumber -> Lines -> IO Int) => Op (Scrollvalue ()) Scrollbar orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Scrollbar

Methods

runOp :: Scrollvalue () -> orig -> Ref Scrollbar -> impl Source #

impl ~ (Y -> Lines -> LineNumber -> Lines -> IO Int) => Op (Scrollvalue ()) Slider orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Slider

Methods

runOp :: Scrollvalue () -> orig -> Ref Slider -> impl Source #

impl ~ (Double -> Int -> IO Double) => Op (Increment ()) Valuator orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Valuator

Methods

runOp :: Increment () -> orig -> Ref Valuator -> impl Source #

impl ~ (Double -> IO Double) => Op (Clamp ()) Valuator orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Valuator

Methods

runOp :: Clamp () -> orig -> Ref Valuator -> impl Source #

impl ~ (Double -> IO Double) => Op (Round ()) Valuator orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Valuator

Methods

runOp :: Round () -> orig -> Ref Valuator -> impl Source #

impl ~ IO (Either UnknownError Text) => Op (Format ()) Valuator orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Valuator

Methods

runOp :: Format () -> orig -> Ref Valuator -> impl Source #

impl ~ (Int -> IO ()) => Op (Precision ()) Valuator orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Valuator

Methods

runOp :: Precision () -> orig -> Ref Valuator -> impl Source #

impl ~ IO Double => Op (GetStep ()) Spinner orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Spinner

Methods

runOp :: GetStep () -> orig -> Ref Spinner -> impl Source #

impl ~ IO Rational => Op (GetStep ()) Valuator orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Valuator

Methods

runOp :: GetStep () -> orig -> Ref Valuator -> impl Source #

impl ~ (Double -> IO ()) => Op (SetStep ()) Spinner orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Spinner

Methods

runOp :: SetStep () -> orig -> Ref Spinner -> impl Source #

impl ~ (Rational -> IO ()) => Op (SetStep ()) Valuator orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Valuator

Methods

runOp :: SetStep () -> orig -> Ref Valuator -> impl Source #

impl ~ (Double -> Double -> IO ()) => Op (Range ()) Spinner orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Spinner

Methods

runOp :: Range () -> orig -> Ref Spinner -> impl Source #

impl ~ (Double -> Double -> IO ()) => Op (Range ()) Valuator orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Valuator

Methods

runOp :: Range () -> orig -> Ref Valuator -> impl Source #

impl ~ (Double -> IO ()) => Op (SetMaximum ()) Spinner orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Spinner

Methods

runOp :: SetMaximum () -> orig -> Ref Spinner -> impl Source #

impl ~ (Float -> IO ()) => Op (SetMaximum ()) Progress orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Progress

Methods

runOp :: SetMaximum () -> orig -> Ref Progress -> impl Source #

impl ~ (Double -> IO ()) => Op (SetMaximum ()) Valuator orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Valuator

Methods

runOp :: SetMaximum () -> orig -> Ref Valuator -> impl Source #

impl ~ IO Double => Op (GetMaximum ()) Spinner orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Spinner

Methods

runOp :: GetMaximum () -> orig -> Ref Spinner -> impl Source #

impl ~ IO Float => Op (GetMaximum ()) Progress orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Progress

Methods

runOp :: GetMaximum () -> orig -> Ref Progress -> impl Source #

impl ~ IO Double => Op (GetMaximum ()) Valuator orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Valuator

Methods

runOp :: GetMaximum () -> orig -> Ref Valuator -> impl Source #

impl ~ (Double -> IO ()) => Op (SetMinimum ()) Spinner orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Spinner

Methods

runOp :: SetMinimum () -> orig -> Ref Spinner -> impl Source #

impl ~ (Float -> IO ()) => Op (SetMinimum ()) Progress orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Progress

Methods

runOp :: SetMinimum () -> orig -> Ref Progress -> impl Source #

impl ~ (Double -> IO ()) => Op (SetMinimum ()) Valuator orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Valuator

Methods

runOp :: SetMinimum () -> orig -> Ref Valuator -> impl Source #

impl ~ IO Double => Op (GetMinimum ()) Spinner orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Spinner

Methods

runOp :: GetMinimum () -> orig -> Ref Spinner -> impl Source #

impl ~ IO Float => Op (GetMinimum ()) Progress orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Progress

Methods

runOp :: GetMinimum () -> orig -> Ref Progress -> impl Source #

impl ~ IO Double => Op (GetMinimum ()) Valuator orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Valuator

Methods

runOp :: GetMinimum () -> orig -> Ref Valuator -> impl Source #

impl ~ (Double -> Double -> IO ()) => Op (Bounds ()) Slider orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Slider

Methods

runOp :: Bounds () -> orig -> Ref Slider -> impl Source #

impl ~ (Double -> Double -> IO ()) => Op (Bounds ()) Valuator orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Valuator

Methods

runOp :: Bounds () -> orig -> Ref Valuator -> impl Source #

impl ~ (Color -> IO ()) => Op (SetDownColor ()) MenuPrim orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuPrim

Methods

runOp :: SetDownColor () -> orig -> Ref MenuPrim -> impl Source #

impl ~ (Color -> IO ()) => Op (SetDownColor ()) Button orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Button

Methods

runOp :: SetDownColor () -> orig -> Ref Button -> impl Source #

impl ~ IO Color => Op (GetDownColor ()) MenuPrim orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuPrim

Methods

runOp :: GetDownColor () -> orig -> Ref MenuPrim -> impl Source #

impl ~ IO Color => Op (GetDownColor ()) Button orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Button

Methods

runOp :: GetDownColor () -> orig -> Ref Button -> impl Source #

impl ~ (Boxtype -> IO ()) => Op (SetDownBox ()) FileInput orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.FileInput

Methods

runOp :: SetDownBox () -> orig -> Ref FileInput -> impl Source #

impl ~ (Boxtype -> IO ()) => Op (SetDownBox ()) MenuPrim orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuPrim

Methods

runOp :: SetDownBox () -> orig -> Ref MenuPrim -> impl Source #

impl ~ (Boxtype -> IO ()) => Op (SetDownBox ()) Button orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Button

Methods

runOp :: SetDownBox () -> orig -> Ref Button -> impl Source #

impl ~ IO Boxtype => Op (GetDownBox ()) FileInput orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.FileInput

Methods

runOp :: GetDownBox () -> orig -> Ref FileInput -> impl Source #

impl ~ IO Boxtype => Op (GetDownBox ()) MenuPrim orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuPrim

Methods

runOp :: GetDownBox () -> orig -> Ref MenuPrim -> impl Source #

impl ~ IO Boxtype => Op (GetDownBox ()) Button orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Button

Methods

runOp :: GetDownBox () -> orig -> Ref Button -> impl Source #

impl ~ (ShortcutKeySequence -> IO ()) => Op (SetShortcut ()) TextDisplay orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextDisplay

Methods

runOp :: SetShortcut () -> orig -> Ref TextDisplay -> impl Source #

impl ~ (ShortcutKeySequence -> IO ()) => Op (SetShortcut ()) ValueInput orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ValueInput

Methods

runOp :: SetShortcut () -> orig -> Ref ValueInput -> impl Source #

impl ~ (ShortcutKeySequence -> IO ()) => Op (SetShortcut ()) Input orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Input

Methods

runOp :: SetShortcut () -> orig -> Ref Input -> impl Source #

impl ~ (AtIndex -> ShortcutKeySequence -> IO ()) => Op (SetShortcut ()) SysMenuBar orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.SysMenuBar

Methods

runOp :: SetShortcut () -> orig -> Ref SysMenuBar -> impl Source #

impl ~ (AtIndex -> ShortcutKeySequence -> IO ()) => Op (SetShortcut ()) MenuPrim orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuPrim

Methods

runOp :: SetShortcut () -> orig -> Ref MenuPrim -> impl Source #

impl ~ (ShortcutKeySequence -> IO ()) => Op (SetShortcut ()) MenuItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuItem

Methods

runOp :: SetShortcut () -> orig -> Ref MenuItem -> impl Source #

impl ~ (ShortcutKeySequence -> IO ()) => Op (SetShortcut ()) Button orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Button

Methods

runOp :: SetShortcut () -> orig -> Ref Button -> impl Source #

impl ~ IO (Maybe ShortcutKeySequence) => Op (GetShortcut ()) TextDisplay orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextDisplay

Methods

runOp :: GetShortcut () -> orig -> Ref TextDisplay -> impl Source #

impl ~ IO (Maybe ShortcutKeySequence) => Op (GetShortcut ()) ValueInput orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ValueInput

Methods

runOp :: GetShortcut () -> orig -> Ref ValueInput -> impl Source #

impl ~ IO (Maybe ShortcutKeySequence) => Op (GetShortcut ()) Input orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Input

Methods

runOp :: GetShortcut () -> orig -> Ref Input -> impl Source #

impl ~ IO (Maybe ShortcutKeySequence) => Op (GetShortcut ()) MenuItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuItem

Methods

runOp :: GetShortcut () -> orig -> Ref MenuItem -> impl Source #

impl ~ IO (Maybe ShortcutKeySequence) => Op (GetShortcut ()) Button orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Button

Methods

runOp :: GetShortcut () -> orig -> Ref Button -> impl Source #

(Parent a MenuItem, impl ~ (Ref a -> IO ())) => Op (Setonly ()) MenuPrim orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuPrim

Methods

runOp :: Setonly () -> orig -> Ref MenuPrim -> impl Source #

impl ~ IO () => Op (Setonly ()) MenuItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuItem

Methods

runOp :: Setonly () -> orig -> Ref MenuItem -> impl Source #

impl ~ IO () => Op (Setonly ()) Button orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Button

Methods

runOp :: Setonly () -> orig -> Ref Button -> impl Source #

impl ~ (IndexRange -> IO ()) => Op (Set ()) TextSelection orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextSelection

Methods

runOp :: Set () -> orig -> Ref TextSelection -> impl Source #

impl ~ IO () => Op (Set ()) MenuItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuItem

Methods

runOp :: Set () -> orig -> Ref MenuItem -> impl Source #

impl ~ IO Bool => Op (Set ()) Button orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Button

Methods

runOp :: Set () -> orig -> Ref Button -> impl Source #

impl ~ (Text -> IO ()) => Op (SetValue ()) FileInput orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.FileInput

Methods

runOp :: SetValue () -> orig -> Ref FileInput -> impl Source #

impl ~ (Double -> IO ()) => Op (SetValue ()) Spinner orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Spinner

Methods

runOp :: SetValue () -> orig -> Ref Spinner -> impl Source #

(Parent a Widget, impl ~ (Maybe (Ref a) -> IO (Either NoChange ()))) => Op (SetValue ()) Tabs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tabs

Methods

runOp :: SetValue () -> orig -> Ref Tabs -> impl Source #

impl ~ (ClockSetTimeType -> IO ()) => Op (SetValue ()) Clock orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Clock

Methods

runOp :: SetValue () -> orig -> Ref Clock -> impl Source #

impl ~ (LineNumber -> IO ()) => Op (SetValue ()) Browser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Browser

Methods

runOp :: SetValue () -> orig -> Ref Browser -> impl Source #

(Parent a Widget, impl ~ (Maybe (Ref a) -> IO ())) => Op (SetValue ()) Wizard orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Wizard

Methods

runOp :: SetValue () -> orig -> Ref Wizard -> impl Source #

impl ~ (Float -> IO ()) => Op (SetValue ()) Progress orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Progress

Methods

runOp :: SetValue () -> orig -> Ref Progress -> impl Source #

impl ~ (Text -> IO (Either NoChange ())) => Op (SetValue ()) Input orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Input

Methods

runOp :: SetValue () -> orig -> Ref Input -> impl Source #

impl ~ (MenuItemReference -> IO (Either NoChange ())) => Op (SetValue ()) Choice orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Choice

Methods

runOp :: SetValue () -> orig -> Ref Choice -> impl Source #

impl ~ (MenuItemReference -> IO (Either NoChange ())) => Op (SetValue ()) MenuPrim orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuPrim

Methods

runOp :: SetValue () -> orig -> Ref MenuPrim -> impl Source #

impl ~ (Double -> IO (Either NoChange ())) => Op (SetValue ()) Valuator orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Valuator

Methods

runOp :: SetValue () -> orig -> Ref Valuator -> impl Source #

impl ~ (Bool -> IO Bool) => Op (SetValue ()) Button orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Button

Methods

runOp :: SetValue () -> orig -> Ref Button -> impl Source #

impl ~ IO Text => Op (GetValue ()) FileInput orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.FileInput

Methods

runOp :: GetValue () -> orig -> Ref FileInput -> impl Source #

impl ~ IO (Either OutOfRange Between0And1) => Op (GetValue ()) ColorChooser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ColorChooser

Methods

runOp :: GetValue () -> orig -> Ref ColorChooser -> impl Source #

impl ~ IO Double => Op (GetValue ()) Spinner orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Spinner

Methods

runOp :: GetValue () -> orig -> Ref Spinner -> impl Source #

impl ~ IO (Maybe (Ref Widget)) => Op (GetValue ()) Tabs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tabs

Methods

runOp :: GetValue () -> orig -> Ref Tabs -> impl Source #

impl ~ IO ClockByTime => Op (GetValue ()) Clock orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Clock

Methods

runOp :: GetValue () -> orig -> Ref Clock -> impl Source #

impl ~ IO LineNumber => Op (GetValue ()) Browser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Browser

Methods

runOp :: GetValue () -> orig -> Ref Browser -> impl Source #

impl ~ IO (Maybe (Ref Widget)) => Op (GetValue ()) Wizard orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Wizard

Methods

runOp :: GetValue () -> orig -> Ref Wizard -> impl Source #

impl ~ IO Float => Op (GetValue ()) Progress orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Progress

Methods

runOp :: GetValue () -> orig -> Ref Progress -> impl Source #

impl ~ IO Text => Op (GetValue ()) Input orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Input

Methods

runOp :: GetValue () -> orig -> Ref Input -> impl Source #

impl ~ IO AtIndex => Op (GetValue ()) Choice orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Choice

Methods

runOp :: GetValue () -> orig -> Ref Choice -> impl Source #

impl ~ IO (Maybe AtIndex) => Op (GetValue ()) MenuPrim orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuPrim

Methods

runOp :: GetValue () -> orig -> Ref MenuPrim -> impl Source #

impl ~ IO Int => Op (GetValue ()) MenuItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuItem

Methods

runOp :: GetValue () -> orig -> Ref MenuItem -> impl Source #

impl ~ IO Double => Op (GetValue ()) Valuator orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Valuator

Methods

runOp :: GetValue () -> orig -> Ref Valuator -> impl Source #

impl ~ IO Bool => Op (GetValue ()) Button orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Button

Methods

runOp :: GetValue () -> orig -> Ref Button -> impl Source #

impl ~ IO () => Op (Flush ()) GlWindow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.GlWindow

Methods

runOp :: Flush () -> orig -> Ref GlWindow -> impl Source #

impl ~ IO () => Op (Flush ()) OverlayWindow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.OverlayWindow

Methods

runOp :: Flush () -> orig -> Ref OverlayWindow -> impl Source #

impl ~ IO () => Op (RedrawOverlay ()) GlWindow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.GlWindow

Methods

runOp :: RedrawOverlay () -> orig -> Ref GlWindow -> impl Source #

impl ~ IO () => Op (RedrawOverlay ()) OverlayWindow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.OverlayWindow

Methods

runOp :: RedrawOverlay () -> orig -> Ref OverlayWindow -> impl Source #

impl ~ IO Bool => Op (CanDoOverlay ()) GlWindow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.GlWindow

Methods

runOp :: CanDoOverlay () -> orig -> Ref GlWindow -> impl Source #

impl ~ IO Bool => Op (CanDoOverlay ()) OverlayWindow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.OverlayWindow

Methods

runOp :: CanDoOverlay () -> orig -> Ref OverlayWindow -> impl Source #

impl ~ IO () => Op (WaitForExpose ()) Window orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Window

Methods

runOp :: WaitForExpose () -> orig -> Ref Window -> impl Source #

impl ~ IO Int => Op (GetDecoratedH ()) Window orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Window

Methods

runOp :: GetDecoratedH () -> orig -> Ref Window -> impl Source #

impl ~ IO Int => Op (GetDecoratedW ()) Window orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Window

Methods

runOp :: GetDecoratedW () -> orig -> Ref Window -> impl Source #

impl ~ (CursorType -> (Maybe Color, Maybe Color) -> IO ()) => Op (SetDefaultCursorWithFgBg ()) Window orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Window

Methods

runOp :: SetDefaultCursorWithFgBg () -> orig -> Ref Window -> impl Source #

impl ~ (CursorType -> IO ()) => Op (SetDefaultCursor ()) Window orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Window

Methods

runOp :: SetDefaultCursor () -> orig -> Ref Window -> impl Source #

impl ~ (Cursor -> (Maybe Color, Maybe Color) -> IO ()) => Op (SetCursorWithFgBg ()) Window orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Window

Methods

runOp :: SetCursorWithFgBg () -> orig -> Ref Window -> impl Source #

impl ~ (Cursor -> IO ()) => Op (SetCursor ()) Window orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Window

Methods

runOp :: SetCursor () -> orig -> Ref Window -> impl Source #

impl ~ IO () => Op (MakeCurrent ()) Window orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Window

Methods

runOp :: MakeCurrent () -> orig -> Ref Window -> impl Source #

impl ~ IO Int => Op (GetYRoot ()) Window orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Window

Methods

runOp :: GetYRoot () -> orig -> Ref Window -> impl Source #

impl ~ IO Int => Op (GetXRoot ()) Window orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Window

Methods

runOp :: GetXRoot () -> orig -> Ref Window -> impl Source #

impl ~ IO () => Op (Iconize ()) Window orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Window

Methods

runOp :: Iconize () -> orig -> Ref Window -> impl Source #

impl ~ IO Bool => Op (Shown ()) Window orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Window

Methods

runOp :: Shown () -> orig -> Ref Window -> impl Source #

impl ~ (LineNumber -> Ref Image -> IO ()) => Op (SetIcon ()) Browser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Browser

Methods

runOp :: SetIcon () -> orig -> Ref Browser -> impl Source #

(Parent a Image, impl ~ (Maybe (Ref a) -> IO ())) => Op (SetIcon ()) Window orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Window

Methods

runOp :: SetIcon () -> orig -> Ref Window -> impl Source #

impl ~ (LineNumber -> IO (Maybe (Ref Image))) => Op (GetIcon ()) Browser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Browser

Methods

runOp :: GetIcon () -> orig -> Ref Browser -> impl Source #

impl ~ IO (Maybe (Ref Image)) => Op (GetIcon ()) Window orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Window

Methods

runOp :: GetIcon () -> orig -> Ref Window -> impl Source #

impl ~ (Text -> IO ()) => Op (SetXclass ()) Window orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Window

Methods

runOp :: SetXclass () -> orig -> Ref Window -> impl Source #

impl ~ IO Text => Op (GetXclass ()) Window orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Window

Methods

runOp :: GetXclass () -> orig -> Ref Window -> impl Source #

impl ~ (Text -> Text -> IO ()) => Op (SetLabelWithIconlabel ()) Window orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Window

Methods

runOp :: SetLabelWithIconlabel () -> orig -> Ref Window -> impl Source #

impl ~ (Text -> IO ()) => Op (SetIconlabel ()) Window orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Window

Methods

runOp :: SetIconlabel () -> orig -> Ref Window -> impl Source #

impl ~ IO Text => Op (GetIconlabel ()) Window orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Window

Methods

runOp :: GetIconlabel () -> orig -> Ref Window -> impl Source #

impl ~ (Size -> OptionalSizeRangeArgs -> IO ()) => Op (SizeRangeWithArgs ()) Window orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Window

Methods

runOp :: SizeRangeWithArgs () -> orig -> Ref Window -> impl Source #

impl ~ (Size -> IO ()) => Op (SizeRange ()) Window orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Window

Methods

runOp :: SizeRange () -> orig -> Ref Window -> impl Source #

impl ~ IO () => Op (FreePosition ()) Window orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Window

Methods

runOp :: FreePosition () -> orig -> Ref Window -> impl Source #

impl ~ (PositionSpec -> Maybe Bool -> IO ()) => Op (HotSpot ()) Window orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Window

Methods

runOp :: HotSpot () -> orig -> Ref Window -> impl Source #

impl ~ IO Bool => Op (GetTooltipWindow ()) Window orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Window

Methods

runOp :: GetTooltipWindow () -> orig -> Ref Window -> impl Source #

impl ~ IO () => Op (SetTooltipWindow ()) Window orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Window

Methods

runOp :: SetTooltipWindow () -> orig -> Ref Window -> impl Source #

impl ~ IO Bool => Op (GetMenuWindow ()) Window orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Window

Methods

runOp :: GetMenuWindow () -> orig -> Ref Window -> impl Source #

impl ~ IO () => Op (SetMenuWindow ()) Window orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Window

Methods

runOp :: SetMenuWindow () -> orig -> Ref Window -> impl Source #

impl ~ IO Bool => Op (NonModal ()) Window orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Window

Methods

runOp :: NonModal () -> orig -> Ref Window -> impl Source #

impl ~ IO () => Op (SetNonModal ()) Window orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Window

Methods

runOp :: SetNonModal () -> orig -> Ref Window -> impl Source #

impl ~ IO Bool => Op (GetModal ()) Window orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Window

Methods

runOp :: GetModal () -> orig -> Ref Window -> impl Source #

impl ~ IO () => Op (SetModal ()) Window orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Window

Methods

runOp :: SetModal () -> orig -> Ref Window -> impl Source #

impl ~ IO Bool => Op (GetOverride ()) Window orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Window

Methods

runOp :: GetOverride () -> orig -> Ref Window -> impl Source #

impl ~ IO () => Op (SetOverride ()) Window orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Window

Methods

runOp :: SetOverride () -> orig -> Ref Window -> impl Source #

impl ~ IO Bool => Op (GetBorder ()) Window orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Window

Methods

runOp :: GetBorder () -> orig -> Ref Window -> impl Source #

impl ~ IO () => Op (ClearBorder ()) Window orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Window

Methods

runOp :: ClearBorder () -> orig -> Ref Window -> impl Source #

impl ~ (Bool -> IO ()) => Op (SetBorder ()) Window orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Window

Methods

runOp :: SetBorder () -> orig -> Ref Window -> impl Source #

impl ~ (Maybe Rectangle -> IO ()) => Op (FullscreenOff ()) Window orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Window

Methods

runOp :: FullscreenOff () -> orig -> Ref Window -> impl Source #

impl ~ IO () => Op (MakeFullscreen ()) Window orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Window

Methods

runOp :: MakeFullscreen () -> orig -> Ref Window -> impl Source #

impl ~ IO Bool => Op (Changed ()) Window orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Window

Methods

runOp :: Changed () -> orig -> Ref Window -> impl Source #

impl ~ IO Bool => Op (Changed ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: Changed () -> orig -> Ref Widget -> impl Source #

impl ~ IO () => Op (FlushSuper ()) GlWindow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.GlWindow

Methods

runOp :: FlushSuper () -> orig -> Ref GlWindow -> impl Source #

impl ~ IO () => Op (FlushSuper ()) DoubleWindow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.DoubleWindow

Methods

runOp :: FlushSuper () -> orig -> Ref DoubleWindow -> impl Source #

impl ~ IO () => Op (FlushSuper ()) SingleWindow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.SingleWindow

Methods

runOp :: FlushSuper () -> orig -> Ref SingleWindow -> impl Source #

impl ~ IO () => Op (FlushSuper ()) Window orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Window

Methods

runOp :: FlushSuper () -> orig -> Ref Window -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (HandleSuper ()) SimpleTerminal orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.SimpleTerminal

Methods

runOp :: HandleSuper () -> orig -> Ref SimpleTerminal -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (HandleSuper ()) FileInput orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.FileInput

Methods

runOp :: HandleSuper () -> orig -> Ref FileInput -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (HandleSuper ()) FileBrowser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.FileBrowser

Methods

runOp :: HandleSuper () -> orig -> Ref FileBrowser -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (HandleSuper ()) ColorChooser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ColorChooser

Methods

runOp :: HandleSuper () -> orig -> Ref ColorChooser -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (HandleSuper ()) Spinner orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Spinner

Methods

runOp :: HandleSuper () -> orig -> Ref Spinner -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (HandleSuper ()) Tabs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tabs

Methods

runOp :: HandleSuper () -> orig -> Ref Tabs -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (HandleSuper ()) Scrolled orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Scrolled

Methods

runOp :: HandleSuper () -> orig -> Ref Scrolled -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (HandleSuper ()) Pack orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Pack

Methods

runOp :: HandleSuper () -> orig -> Ref Pack -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (HandleSuper ()) Tile orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tile

Methods

runOp :: HandleSuper () -> orig -> Ref Tile -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (HandleSuper ()) TextEditor orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextEditor

Methods

runOp :: HandleSuper () -> orig -> Ref TextEditor -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (HandleSuper ()) TextDisplay orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextDisplay

Methods

runOp :: HandleSuper () -> orig -> Ref TextDisplay -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (HandleSuper ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: HandleSuper () -> orig -> Ref Tree -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (HandleSuper ()) Clock orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Clock

Methods

runOp :: HandleSuper () -> orig -> Ref Clock -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (HandleSuper ()) Browser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Browser

Methods

runOp :: HandleSuper () -> orig -> Ref Browser -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (HandleSuper ()) GlWindow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.GlWindow

Methods

runOp :: HandleSuper () -> orig -> Ref GlWindow -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (HandleSuper ()) TableRow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TableRow

Methods

runOp :: HandleSuper () -> orig -> Ref TableRow -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (HandleSuper ()) Wizard orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Wizard

Methods

runOp :: HandleSuper () -> orig -> Ref Wizard -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (HandleSuper ()) Positioner orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Positioner

Methods

runOp :: HandleSuper () -> orig -> Ref Positioner -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (HandleSuper ()) Progress orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Progress

Methods

runOp :: HandleSuper () -> orig -> Ref Progress -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (HandleSuper ()) ValueOutput orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ValueOutput

Methods

runOp :: HandleSuper () -> orig -> Ref ValueOutput -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (HandleSuper ()) ValueInput orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ValueInput

Methods

runOp :: HandleSuper () -> orig -> Ref ValueInput -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (HandleSuper ()) Output orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Output

Methods

runOp :: HandleSuper () -> orig -> Ref Output -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (HandleSuper ()) Input orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Input

Methods

runOp :: HandleSuper () -> orig -> Ref Input -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (HandleSuper ()) ValueSlider orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ValueSlider

Methods

runOp :: HandleSuper () -> orig -> Ref ValueSlider -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (HandleSuper ()) Scrollbar orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Scrollbar

Methods

runOp :: HandleSuper () -> orig -> Ref Scrollbar -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (HandleSuper ()) Counter orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Counter

Methods

runOp :: HandleSuper () -> orig -> Ref Counter -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (HandleSuper ()) Roller orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Roller

Methods

runOp :: HandleSuper () -> orig -> Ref Roller -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (HandleSuper ()) Dial orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Dial

Methods

runOp :: HandleSuper () -> orig -> Ref Dial -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (HandleSuper ()) Adjuster orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Adjuster

Methods

runOp :: HandleSuper () -> orig -> Ref Adjuster -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (HandleSuper ()) MenuButton orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuButton

Methods

runOp :: HandleSuper () -> orig -> Ref MenuButton -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (HandleSuper ()) Choice orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Choice

Methods

runOp :: HandleSuper () -> orig -> Ref Choice -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (HandleSuper ()) SysMenuBar orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.SysMenuBar

Methods

runOp :: HandleSuper () -> orig -> Ref SysMenuBar -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (HandleSuper ()) MenuBar orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuBar

Methods

runOp :: HandleSuper () -> orig -> Ref MenuBar -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (HandleSuper ()) MenuPrim orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuPrim

Methods

runOp :: HandleSuper () -> orig -> Ref MenuPrim -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (HandleSuper ()) Slider orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Slider

Methods

runOp :: HandleSuper () -> orig -> Ref Slider -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (HandleSuper ()) Valuator orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Valuator

Methods

runOp :: HandleSuper () -> orig -> Ref Valuator -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (HandleSuper ()) RepeatButton orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.RepeatButton

Methods

runOp :: HandleSuper () -> orig -> Ref RepeatButton -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (HandleSuper ()) RoundButton orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.RoundButton

Methods

runOp :: HandleSuper () -> orig -> Ref RoundButton -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (HandleSuper ()) ReturnButton orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ReturnButton

Methods

runOp :: HandleSuper () -> orig -> Ref ReturnButton -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (HandleSuper ()) CheckButton orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.CheckButton

Methods

runOp :: HandleSuper () -> orig -> Ref CheckButton -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (HandleSuper ()) LightButton orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.LightButton

Methods

runOp :: HandleSuper () -> orig -> Ref LightButton -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (HandleSuper ()) Button orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Button

Methods

runOp :: HandleSuper () -> orig -> Ref Button -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (HandleSuper ()) DoubleWindow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.DoubleWindow

Methods

runOp :: HandleSuper () -> orig -> Ref DoubleWindow -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (HandleSuper ()) SingleWindow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.SingleWindow

Methods

runOp :: HandleSuper () -> orig -> Ref SingleWindow -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (HandleSuper ()) Window orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Window

Methods

runOp :: HandleSuper () -> orig -> Ref Window -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (HandleSuper ()) Group orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Group

Methods

runOp :: HandleSuper () -> orig -> Ref Group -> impl Source #

impl ~ IO () => Op (DrawSuper ()) SimpleTerminal orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.SimpleTerminal

Methods

runOp :: DrawSuper () -> orig -> Ref SimpleTerminal -> impl Source #

impl ~ IO () => Op (DrawSuper ()) FileInput orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.FileInput

Methods

runOp :: DrawSuper () -> orig -> Ref FileInput -> impl Source #

impl ~ IO () => Op (DrawSuper ()) FileBrowser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.FileBrowser

Methods

runOp :: DrawSuper () -> orig -> Ref FileBrowser -> impl Source #

impl ~ IO () => Op (DrawSuper ()) ColorChooser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ColorChooser

Methods

runOp :: DrawSuper () -> orig -> Ref ColorChooser -> impl Source #

impl ~ IO () => Op (DrawSuper ()) Spinner orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Spinner

Methods

runOp :: DrawSuper () -> orig -> Ref Spinner -> impl Source #

impl ~ IO () => Op (DrawSuper ()) Tabs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tabs

Methods

runOp :: DrawSuper () -> orig -> Ref Tabs -> impl Source #

impl ~ IO () => Op (DrawSuper ()) Scrolled orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Scrolled

Methods

runOp :: DrawSuper () -> orig -> Ref Scrolled -> impl Source #

impl ~ IO () => Op (DrawSuper ()) Pack orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Pack

Methods

runOp :: DrawSuper () -> orig -> Ref Pack -> impl Source #

impl ~ IO () => Op (DrawSuper ()) Tile orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tile

Methods

runOp :: DrawSuper () -> orig -> Ref Tile -> impl Source #

impl ~ IO () => Op (DrawSuper ()) TextEditor orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextEditor

Methods

runOp :: DrawSuper () -> orig -> Ref TextEditor -> impl Source #

impl ~ IO () => Op (DrawSuper ()) TextDisplay orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextDisplay

Methods

runOp :: DrawSuper () -> orig -> Ref TextDisplay -> impl Source #

impl ~ IO () => Op (DrawSuper ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: DrawSuper () -> orig -> Ref Tree -> impl Source #

impl ~ IO () => Op (DrawSuper ()) Clock orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Clock

Methods

runOp :: DrawSuper () -> orig -> Ref Clock -> impl Source #

impl ~ IO () => Op (DrawSuper ()) Browser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Browser

Methods

runOp :: DrawSuper () -> orig -> Ref Browser -> impl Source #

impl ~ IO () => Op (DrawSuper ()) GlWindow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.GlWindow

Methods

runOp :: DrawSuper () -> orig -> Ref GlWindow -> impl Source #

impl ~ IO () => Op (DrawSuper ()) TableRow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TableRow

Methods

runOp :: DrawSuper () -> orig -> Ref TableRow -> impl Source #

impl ~ IO () => Op (DrawSuper ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: DrawSuper () -> orig -> Ref Table -> impl Source #

impl ~ IO () => Op (DrawSuper ()) Wizard orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Wizard

Methods

runOp :: DrawSuper () -> orig -> Ref Wizard -> impl Source #

impl ~ IO () => Op (DrawSuper ()) Positioner orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Positioner

Methods

runOp :: DrawSuper () -> orig -> Ref Positioner -> impl Source #

impl ~ IO () => Op (DrawSuper ()) Progress orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Progress

Methods

runOp :: DrawSuper () -> orig -> Ref Progress -> impl Source #

impl ~ IO () => Op (DrawSuper ()) ValueOutput orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ValueOutput

Methods

runOp :: DrawSuper () -> orig -> Ref ValueOutput -> impl Source #

impl ~ IO () => Op (DrawSuper ()) ValueInput orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ValueInput

Methods

runOp :: DrawSuper () -> orig -> Ref ValueInput -> impl Source #

impl ~ IO () => Op (DrawSuper ()) Output orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Output

Methods

runOp :: DrawSuper () -> orig -> Ref Output -> impl Source #

impl ~ IO () => Op (DrawSuper ()) Input orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Input

Methods

runOp :: DrawSuper () -> orig -> Ref Input -> impl Source #

impl ~ IO () => Op (DrawSuper ()) ValueSlider orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ValueSlider

Methods

runOp :: DrawSuper () -> orig -> Ref ValueSlider -> impl Source #

impl ~ IO () => Op (DrawSuper ()) Scrollbar orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Scrollbar

Methods

runOp :: DrawSuper () -> orig -> Ref Scrollbar -> impl Source #

impl ~ IO () => Op (DrawSuper ()) Counter orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Counter

Methods

runOp :: DrawSuper () -> orig -> Ref Counter -> impl Source #

impl ~ IO () => Op (DrawSuper ()) Roller orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Roller

Methods

runOp :: DrawSuper () -> orig -> Ref Roller -> impl Source #

impl ~ IO () => Op (DrawSuper ()) Dial orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Dial

Methods

runOp :: DrawSuper () -> orig -> Ref Dial -> impl Source #

impl ~ IO () => Op (DrawSuper ()) Adjuster orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Adjuster

Methods

runOp :: DrawSuper () -> orig -> Ref Adjuster -> impl Source #

impl ~ IO () => Op (DrawSuper ()) MenuButton orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuButton

Methods

runOp :: DrawSuper () -> orig -> Ref MenuButton -> impl Source #

impl ~ IO () => Op (DrawSuper ()) Choice orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Choice

Methods

runOp :: DrawSuper () -> orig -> Ref Choice -> impl Source #

impl ~ IO () => Op (DrawSuper ()) SysMenuBar orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.SysMenuBar

Methods

runOp :: DrawSuper () -> orig -> Ref SysMenuBar -> impl Source #

impl ~ IO () => Op (DrawSuper ()) MenuBar orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuBar

Methods

runOp :: DrawSuper () -> orig -> Ref MenuBar -> impl Source #

impl ~ IO () => Op (DrawSuper ()) Slider orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Slider

Methods

runOp :: DrawSuper () -> orig -> Ref Slider -> impl Source #

impl ~ IO () => Op (DrawSuper ()) RepeatButton orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.RepeatButton

Methods

runOp :: DrawSuper () -> orig -> Ref RepeatButton -> impl Source #

impl ~ IO () => Op (DrawSuper ()) RoundButton orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.RoundButton

Methods

runOp :: DrawSuper () -> orig -> Ref RoundButton -> impl Source #

impl ~ IO () => Op (DrawSuper ()) ReturnButton orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ReturnButton

Methods

runOp :: DrawSuper () -> orig -> Ref ReturnButton -> impl Source #

impl ~ IO () => Op (DrawSuper ()) CheckButton orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.CheckButton

Methods

runOp :: DrawSuper () -> orig -> Ref CheckButton -> impl Source #

impl ~ IO () => Op (DrawSuper ()) LightButton orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.LightButton

Methods

runOp :: DrawSuper () -> orig -> Ref LightButton -> impl Source #

impl ~ IO () => Op (DrawSuper ()) Button orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Button

Methods

runOp :: DrawSuper () -> orig -> Ref Button -> impl Source #

impl ~ IO () => Op (DrawSuper ()) DoubleWindow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.DoubleWindow

Methods

runOp :: DrawSuper () -> orig -> Ref DoubleWindow -> impl Source #

impl ~ IO () => Op (DrawSuper ()) SingleWindow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.SingleWindow

Methods

runOp :: DrawSuper () -> orig -> Ref SingleWindow -> impl Source #

impl ~ IO () => Op (DrawSuper ()) Window orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Window

Methods

runOp :: DrawSuper () -> orig -> Ref Window -> impl Source #

impl ~ IO () => Op (DrawSuper ()) Group orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Group

Methods

runOp :: DrawSuper () -> orig -> Ref Group -> impl Source #

impl ~ (AtIndex -> IO (Maybe (Ref Widget))) => Op (GetChild ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: GetChild () -> orig -> Ref Table -> impl Source #

impl ~ (AtIndex -> IO (Maybe (Ref Widget))) => Op (GetChild ()) Group orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Group

Methods

runOp :: GetChild () -> orig -> Ref Group -> impl Source #

impl ~ IO [Ref Widget] => Op (GetArray ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: GetArray () -> orig -> Ref Table -> impl Source #

impl ~ IO [Ref Widget] => Op (GetArray ()) Group orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Group

Methods

runOp :: GetArray () -> orig -> Ref Group -> impl Source #

(Parent a Widget, Parent b Widget, impl ~ (Ref a -> Ref b -> IO ())) => Op (InsertBefore ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: InsertBefore () -> orig -> Ref Table -> impl Source #

(Parent a Widget, impl ~ (Ref a -> Ref b -> IO ())) => Op (InsertBefore ()) Group orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Group

Methods

runOp :: InsertBefore () -> orig -> Ref Group -> impl Source #

impl ~ IO (Maybe (Ref Widget)) => Op (DdfdesignKludge ()) Group orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Group

Methods

runOp :: DdfdesignKludge () -> orig -> Ref Group -> impl Source #

(Parent a Widget, impl ~ (Ref a -> IO ())) => Op (Focus ()) Group orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Group

Methods

runOp :: Focus () -> orig -> Ref Group -> impl Source #

impl ~ IO Bool => Op (ClipChildren ()) Group orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Group

Methods

runOp :: ClipChildren () -> orig -> Ref Group -> impl Source #

impl ~ (Bool -> IO ()) => Op (SetClipChildren ()) Group orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Group

Methods

runOp :: SetClipChildren () -> orig -> Ref Group -> impl Source #

impl ~ IO Int => Op (Children ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: Children () -> orig -> Ref TreeItem -> impl Source #

impl ~ IO Int => Op (Children ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: Children () -> orig -> Ref Table -> impl Source #

impl ~ IO Int => Op (Children ()) Group orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Group

Methods

runOp :: Children () -> orig -> Ref Group -> impl Source #

impl ~ IO () => Op (InitSizes ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: InitSizes () -> orig -> Ref Table -> impl Source #

impl ~ IO () => Op (InitSizes ()) Group orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Group

Methods

runOp :: InitSizes () -> orig -> Ref Group -> impl Source #

(Parent a Widget, impl ~ (Ref a -> IO ())) => Op (AddResizable ()) Group orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Group

Methods

runOp :: AddResizable () -> orig -> Ref Group -> impl Source #

impl ~ IO (Maybe (Ref Widget)) => Op (GetResizable ()) Group orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Group

Methods

runOp :: GetResizable () -> orig -> Ref Group -> impl Source #

impl ~ IO () => Op (SetNotResizable ()) Group orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Group

Methods

runOp :: SetNotResizable () -> orig -> Ref Group -> impl Source #

(Parent a Widget, impl ~ (Maybe (Ref a) -> IO ())) => Op (SetResizable ()) Group orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Group

Methods

runOp :: SetResizable () -> orig -> Ref Group -> impl Source #

impl ~ IO () => Op (Clear ()) SimpleTerminal orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.SimpleTerminal

Methods

runOp :: Clear () -> orig -> Ref SimpleTerminal -> impl Source #

impl ~ IO () => Op (Clear ()) Scrolled orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Scrolled

Methods

runOp :: Clear () -> orig -> Ref Scrolled -> impl Source #

impl ~ IO () => Op (Clear ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: Clear () -> orig -> Ref Tree -> impl Source #

impl ~ IO () => Op (Clear ()) Browser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Browser

Methods

runOp :: Clear () -> orig -> Ref Browser -> impl Source #

impl ~ IO () => Op (Clear ()) TableRow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TableRow

Methods

runOp :: Clear () -> orig -> Ref TableRow -> impl Source #

impl ~ IO () => Op (Clear ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: Clear () -> orig -> Ref Table -> impl Source #

impl ~ IO () => Op (Clear ()) SysMenuBar orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.SysMenuBar

Methods

runOp :: Clear () -> orig -> Ref SysMenuBar -> impl Source #

impl ~ IO () => Op (Clear ()) MenuPrim orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuPrim

Methods

runOp :: Clear () -> orig -> Ref MenuPrim -> impl Source #

impl ~ IO () => Op (Clear ()) MenuItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuItem

Methods

runOp :: Clear () -> orig -> Ref MenuItem -> impl Source #

impl ~ IO Bool => Op (Clear ()) Button orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Button

Methods

runOp :: Clear () -> orig -> Ref Button -> impl Source #

impl ~ IO () => Op (Clear ()) Group orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Group

Methods

runOp :: Clear () -> orig -> Ref Group -> impl Source #

(Parent a Widget, impl ~ (Ref a -> IO ())) => Op (RemoveWidget ()) Group orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Group

Methods

runOp :: RemoveWidget () -> orig -> Ref Group -> impl Source #

impl ~ (AtIndex -> IO ()) => Op (RemoveIndex ()) Group orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Group

Methods

runOp :: RemoveIndex () -> orig -> Ref Group -> impl Source #

impl ~ (AtIndex -> Text -> IO ()) => Op (Insert ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: Insert () -> orig -> Ref TextBuffer -> impl Source #

(Parent a TreeItem, impl ~ (Ref a -> Text -> AtIndex -> IO (Maybe (Ref a)))) => Op (Insert ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: Insert () -> orig -> Ref Tree -> impl Source #

(Parent a TreePrefs, impl ~ (Ref a -> Text -> Maybe AtIndex -> IO (Maybe (Ref TreeItem)))) => Op (Insert ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: Insert () -> orig -> Ref TreeItem -> impl Source #

impl ~ (LineNumber -> Text -> IO ()) => Op (Insert ()) Browser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Browser

Methods

runOp :: Insert () -> orig -> Ref Browser -> impl Source #

(Parent a Widget, impl ~ (Ref a -> AtIndex -> IO ())) => Op (Insert ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: Insert () -> orig -> Ref Table -> impl Source #

impl ~ (Text -> IO (Either NoChange ())) => Op (Insert ()) Input orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Input

Methods

runOp :: Insert () -> orig -> Ref Input -> impl Source #

(Parent a MenuPrim, impl ~ (AtIndex -> Text -> Maybe Shortcut -> (Ref a -> IO ()) -> MenuItemFlags -> IO AtIndex)) => Op (Insert ()) SysMenuBar orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.SysMenuBar

Methods

runOp :: Insert () -> orig -> Ref SysMenuBar -> impl Source #

(Parent a MenuPrim, impl ~ (AtIndex -> Text -> Maybe Shortcut -> (Ref a -> IO ()) -> MenuItemFlags -> IO AtIndex)) => Op (Insert ()) MenuPrim orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuPrim

Methods

runOp :: Insert () -> orig -> Ref MenuPrim -> impl Source #

(Parent a MenuItem, impl ~ (AtIndex -> Text -> Maybe ShortcutKeySequence -> (Ref a -> IO ()) -> MenuItemFlags -> IO AtIndex)) => Op (Insert ()) MenuItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuItem

Methods

runOp :: Insert () -> orig -> Ref MenuItem -> impl Source #

(Parent a Widget, impl ~ (Ref a -> AtIndex -> IO ())) => Op (Insert ()) Group orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Group

Methods

runOp :: Insert () -> orig -> Ref Group -> impl Source #

impl ~ (Text -> IO (Maybe (Ref TreeItem))) => Op (Add ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: Add () -> orig -> Ref Tree -> impl Source #

(Parent a TreeItem, Parent b TreePrefs, impl ~ (Ref b -> TreeItemLocator -> IO (Maybe (Ref a)))) => Op (Add ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: Add () -> orig -> Ref TreeItem -> impl Source #

impl ~ (Text -> IO ()) => Op (Add ()) Browser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Browser

Methods

runOp :: Add () -> orig -> Ref Browser -> impl Source #

(Parent a Widget, impl ~ (Ref a -> IO ())) => Op (Add ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: Add () -> orig -> Ref Table -> impl Source #

(Parent a MenuItem, impl ~ (Text -> Maybe Shortcut -> Maybe (Ref a -> IO ()) -> MenuItemFlags -> IO AtIndex)) => Op (Add ()) SysMenuBar orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.SysMenuBar

Methods

runOp :: Add () -> orig -> Ref SysMenuBar -> impl Source #

(Parent a MenuItem, impl ~ (Text -> Maybe Shortcut -> Maybe (Ref a -> IO ()) -> MenuItemFlags -> IO AtIndex)) => Op (Add ()) MenuPrim orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuPrim

Methods

runOp :: Add () -> orig -> Ref MenuPrim -> impl Source #

(Parent a MenuItem, impl ~ (Text -> Maybe Shortcut -> Maybe (Ref a -> IO ()) -> MenuItemFlags -> IO AtIndex)) => Op (Add ()) MenuItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuItem

Methods

runOp :: Add () -> orig -> Ref MenuItem -> impl Source #

(Parent a Widget, impl ~ (Ref a -> IO ())) => Op (Add ()) Group orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Group

Methods

runOp :: Add () -> orig -> Ref Group -> impl Source #

(Parent a Widget, impl ~ (Ref a -> IO Int)) => Op (Find ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: Find () -> orig -> Ref Table -> impl Source #

(Parent a Widget, impl ~ (Ref a -> IO AtIndex)) => Op (Find ()) Group orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Group

Methods

runOp :: Find () -> orig -> Ref Group -> impl Source #

(Match obj ~ FindOp orig orig (Begin ()), Match obj ~ FindOp orig orig (End ()), Op (Begin ()) obj orig (IO ()), Op (End ()) obj orig (IO ()), impl ~ (IO a -> IO a)) => Op (Within ()) Group orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Group

Methods

runOp :: Within () -> orig -> Ref Group -> impl Source #

impl ~ IO AtIndex => Op (End ()) TextSelection orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextSelection

Methods

runOp :: End () -> orig -> Ref TextSelection -> impl Source #

impl ~ IO () => Op (End ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: End () -> orig -> Ref Table -> impl Source #

impl ~ IO () => Op (End ()) Group orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Group

Methods

runOp :: End () -> orig -> Ref Group -> impl Source #

impl ~ IO () => Op (Begin ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: Begin () -> orig -> Ref Table -> impl Source #

impl ~ IO () => Op (Begin ()) Group orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Group

Methods

runOp :: Begin () -> orig -> Ref Group -> impl Source #

(Parent a Widget, impl ~ (Ref a -> IO ())) => Op (UpdateChild ()) Group orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Group

Methods

runOp :: UpdateChild () -> orig -> Ref Group -> impl Source #

(Parent a Widget, impl ~ (Ref a -> IO ())) => Op (DrawOutsideLabel ()) Group orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Group

Methods

runOp :: DrawOutsideLabel () -> orig -> Ref Group -> impl Source #

impl ~ IO () => Op (DrawChildren ()) Group orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Group

Methods

runOp :: DrawChildren () -> orig -> Ref Group -> impl Source #

(Parent a Widget, impl ~ (Ref a -> IO ())) => Op (DrawChild ()) Group orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Group

Methods

runOp :: DrawChild () -> orig -> Ref Group -> impl Source #

impl ~ (WidgetFlag -> IO ()) => Op (ClearFlag ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: ClearFlag () -> orig -> Ref Widget -> impl Source #

impl ~ (WidgetFlag -> IO ()) => Op (SetFlag ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: SetFlag () -> orig -> Ref Widget -> impl Source #

impl ~ IO [WidgetFlag] => Op (Flags ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: Flags () -> orig -> Ref Widget -> impl Source #

impl ~ (Maybe (Boxtype, Rectangle) -> IO ()) => Op (DrawFocus ()) Button orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Button

Methods

runOp :: DrawFocus () -> orig -> Ref Button -> impl Source #

impl ~ (Maybe (Boxtype, Rectangle) -> IO ()) => Op (DrawFocus ()) Window orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Window

Methods

runOp :: DrawFocus () -> orig -> Ref Window -> impl Source #

impl ~ (Maybe (Boxtype, Rectangle) -> IO ()) => Op (DrawFocus ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: DrawFocus () -> orig -> Ref Widget -> impl Source #

impl ~ IO () => Op (DrawBackdrop ()) Button orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Button

Methods

runOp :: DrawBackdrop () -> orig -> Ref Button -> impl Source #

impl ~ IO () => Op (DrawBackdrop ()) Window orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Window

Methods

runOp :: DrawBackdrop () -> orig -> Ref Window -> impl Source #

impl ~ IO () => Op (DrawBackdrop ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: DrawBackdrop () -> orig -> Ref Widget -> impl Source #

impl ~ (Boxtype -> Color -> Maybe Rectangle -> IO ()) => Op (DrawBoxWithBoxtype ()) Button orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Button

Methods

runOp :: DrawBoxWithBoxtype () -> orig -> Ref Button -> impl Source #

impl ~ (Boxtype -> Color -> Maybe Rectangle -> IO ()) => Op (DrawBoxWithBoxtype ()) Window orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Window

Methods

runOp :: DrawBoxWithBoxtype () -> orig -> Ref Window -> impl Source #

impl ~ (Boxtype -> Color -> Maybe Rectangle -> IO ()) => Op (DrawBoxWithBoxtype ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: DrawBoxWithBoxtype () -> orig -> Ref Widget -> impl Source #

impl ~ IO () => Op (DrawBox ()) Button orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Button

Methods

runOp :: DrawBox () -> orig -> Ref Button -> impl Source #

impl ~ IO () => Op (DrawBox ()) Window orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Window

Methods

runOp :: DrawBox () -> orig -> Ref Window -> impl Source #

impl ~ IO () => Op (DrawBox ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: DrawBox () -> orig -> Ref Widget -> impl Source #

impl ~ IO Bool => Op (HasCallback ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: HasCallback () -> orig -> Ref Widget -> impl Source #

impl ~ ((Ref orig -> IO ()) -> IO ()) => Op (SetCallback ()) MenuItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuItem

Methods

runOp :: SetCallback () -> orig -> Ref MenuItem -> impl Source #

impl ~ ((Ref orig -> IO ()) -> IO ()) => Op (SetCallback ()) Window orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Window

Methods

runOp :: SetCallback () -> orig -> Ref Window -> impl Source #

impl ~ ((Ref orig -> IO ()) -> IO ()) => Op (SetCallback ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: SetCallback () -> orig -> Ref Widget -> impl Source #

impl ~ (Size -> IO ()) => Op (Resize ()) SVGImage orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.SVGImage

Methods

runOp :: Resize () -> orig -> Ref SVGImage -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (Resize ()) FileInput orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.FileInput

Methods

runOp :: Resize () -> orig -> Ref FileInput -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (Resize ()) FileBrowser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.FileBrowser

Methods

runOp :: Resize () -> orig -> Ref FileBrowser -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (Resize ()) ColorChooser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ColorChooser

Methods

runOp :: Resize () -> orig -> Ref ColorChooser -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (Resize ()) Spinner orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Spinner

Methods

runOp :: Resize () -> orig -> Ref Spinner -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (Resize ()) Tabs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tabs

Methods

runOp :: Resize () -> orig -> Ref Tabs -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (Resize ()) Scrolled orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Scrolled

Methods

runOp :: Resize () -> orig -> Ref Scrolled -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (Resize ()) Pack orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Pack

Methods

runOp :: Resize () -> orig -> Ref Pack -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (Resize ()) Tile orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tile

Methods

runOp :: Resize () -> orig -> Ref Tile -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (Resize ()) TextEditor orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextEditor

Methods

runOp :: Resize () -> orig -> Ref TextEditor -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (Resize ()) TextDisplay orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextDisplay

Methods

runOp :: Resize () -> orig -> Ref TextDisplay -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (Resize ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: Resize () -> orig -> Ref Tree -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (Resize ()) Clock orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Clock

Methods

runOp :: Resize () -> orig -> Ref Clock -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (Resize ()) GlWindow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.GlWindow

Methods

runOp :: Resize () -> orig -> Ref GlWindow -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (Resize ()) TableRow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TableRow

Methods

runOp :: Resize () -> orig -> Ref TableRow -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (Resize ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: Resize () -> orig -> Ref Table -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (Resize ()) Wizard orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Wizard

Methods

runOp :: Resize () -> orig -> Ref Wizard -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (Resize ()) Positioner orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Positioner

Methods

runOp :: Resize () -> orig -> Ref Positioner -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (Resize ()) Progress orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Progress

Methods

runOp :: Resize () -> orig -> Ref Progress -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (Resize ()) ValueOutput orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ValueOutput

Methods

runOp :: Resize () -> orig -> Ref ValueOutput -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (Resize ()) ValueInput orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ValueInput

Methods

runOp :: Resize () -> orig -> Ref ValueInput -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (Resize ()) Output orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Output

Methods

runOp :: Resize () -> orig -> Ref Output -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (Resize ()) Input orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Input

Methods

runOp :: Resize () -> orig -> Ref Input -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (Resize ()) ValueSlider orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ValueSlider

Methods

runOp :: Resize () -> orig -> Ref ValueSlider -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (Resize ()) Scrollbar orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Scrollbar

Methods

runOp :: Resize () -> orig -> Ref Scrollbar -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (Resize ()) Counter orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Counter

Methods

runOp :: Resize () -> orig -> Ref Counter -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (Resize ()) Roller orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Roller

Methods

runOp :: Resize () -> orig -> Ref Roller -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (Resize ()) Dial orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Dial

Methods

runOp :: Resize () -> orig -> Ref Dial -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (Resize ()) Adjuster orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Adjuster

Methods

runOp :: Resize () -> orig -> Ref Adjuster -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (Resize ()) MenuButton orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuButton

Methods

runOp :: Resize () -> orig -> Ref MenuButton -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (Resize ()) Choice orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Choice

Methods

runOp :: Resize () -> orig -> Ref Choice -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (Resize ()) SysMenuBar orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.SysMenuBar

Methods

runOp :: Resize () -> orig -> Ref SysMenuBar -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (Resize ()) MenuBar orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuBar

Methods

runOp :: Resize () -> orig -> Ref MenuBar -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (Resize ()) MenuPrim orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuPrim

Methods

runOp :: Resize () -> orig -> Ref MenuPrim -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (Resize ()) Slider orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Slider

Methods

runOp :: Resize () -> orig -> Ref Slider -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (Resize ()) Valuator orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Valuator

Methods

runOp :: Resize () -> orig -> Ref Valuator -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (Resize ()) RepeatButton orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.RepeatButton

Methods

runOp :: Resize () -> orig -> Ref RepeatButton -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (Resize ()) RoundButton orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.RoundButton

Methods

runOp :: Resize () -> orig -> Ref RoundButton -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (Resize ()) ReturnButton orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ReturnButton

Methods

runOp :: Resize () -> orig -> Ref ReturnButton -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (Resize ()) CheckButton orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.CheckButton

Methods

runOp :: Resize () -> orig -> Ref CheckButton -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (Resize ()) LightButton orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.LightButton

Methods

runOp :: Resize () -> orig -> Ref LightButton -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (Resize ()) Button orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Button

Methods

runOp :: Resize () -> orig -> Ref Button -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (Resize ()) OverlayWindow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.OverlayWindow

Methods

runOp :: Resize () -> orig -> Ref OverlayWindow -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (Resize ()) DoubleWindow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.DoubleWindow

Methods

runOp :: Resize () -> orig -> Ref DoubleWindow -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (Resize ()) SingleWindow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.SingleWindow

Methods

runOp :: Resize () -> orig -> Ref SingleWindow -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (Resize ()) Window orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Window

Methods

runOp :: Resize () -> orig -> Ref Window -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (Resize ()) Group orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Group

Methods

runOp :: Resize () -> orig -> Ref Group -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (Resize ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: Resize () -> orig -> Ref Widget -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (ResizeSuper ()) SimpleTerminal orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.SimpleTerminal

Methods

runOp :: ResizeSuper () -> orig -> Ref SimpleTerminal -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (ResizeSuper ()) FileInput orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.FileInput

Methods

runOp :: ResizeSuper () -> orig -> Ref FileInput -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (ResizeSuper ()) FileBrowser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.FileBrowser

Methods

runOp :: ResizeSuper () -> orig -> Ref FileBrowser -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (ResizeSuper ()) ColorChooser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ColorChooser

Methods

runOp :: ResizeSuper () -> orig -> Ref ColorChooser -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (ResizeSuper ()) Spinner orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Spinner

Methods

runOp :: ResizeSuper () -> orig -> Ref Spinner -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (ResizeSuper ()) Tabs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tabs

Methods

runOp :: ResizeSuper () -> orig -> Ref Tabs -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (ResizeSuper ()) Scrolled orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Scrolled

Methods

runOp :: ResizeSuper () -> orig -> Ref Scrolled -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (ResizeSuper ()) Pack orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Pack

Methods

runOp :: ResizeSuper () -> orig -> Ref Pack -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (ResizeSuper ()) Tile orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tile

Methods

runOp :: ResizeSuper () -> orig -> Ref Tile -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (ResizeSuper ()) TextEditor orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextEditor

Methods

runOp :: ResizeSuper () -> orig -> Ref TextEditor -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (ResizeSuper ()) TextDisplay orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextDisplay

Methods

runOp :: ResizeSuper () -> orig -> Ref TextDisplay -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (ResizeSuper ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: ResizeSuper () -> orig -> Ref Tree -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (ResizeSuper ()) Clock orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Clock

Methods

runOp :: ResizeSuper () -> orig -> Ref Clock -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (ResizeSuper ()) GlWindow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.GlWindow

Methods

runOp :: ResizeSuper () -> orig -> Ref GlWindow -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (ResizeSuper ()) TableRow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TableRow

Methods

runOp :: ResizeSuper () -> orig -> Ref TableRow -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (ResizeSuper ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: ResizeSuper () -> orig -> Ref Table -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (ResizeSuper ()) Wizard orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Wizard

Methods

runOp :: ResizeSuper () -> orig -> Ref Wizard -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (ResizeSuper ()) Positioner orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Positioner

Methods

runOp :: ResizeSuper () -> orig -> Ref Positioner -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (ResizeSuper ()) Progress orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Progress

Methods

runOp :: ResizeSuper () -> orig -> Ref Progress -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (ResizeSuper ()) ValueOutput orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ValueOutput

Methods

runOp :: ResizeSuper () -> orig -> Ref ValueOutput -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (ResizeSuper ()) ValueInput orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ValueInput

Methods

runOp :: ResizeSuper () -> orig -> Ref ValueInput -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (ResizeSuper ()) Output orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Output

Methods

runOp :: ResizeSuper () -> orig -> Ref Output -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (ResizeSuper ()) Input orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Input

Methods

runOp :: ResizeSuper () -> orig -> Ref Input -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (ResizeSuper ()) ValueSlider orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ValueSlider

Methods

runOp :: ResizeSuper () -> orig -> Ref ValueSlider -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (ResizeSuper ()) Scrollbar orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Scrollbar

Methods

runOp :: ResizeSuper () -> orig -> Ref Scrollbar -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (ResizeSuper ()) Counter orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Counter

Methods

runOp :: ResizeSuper () -> orig -> Ref Counter -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (ResizeSuper ()) Roller orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Roller

Methods

runOp :: ResizeSuper () -> orig -> Ref Roller -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (ResizeSuper ()) Dial orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Dial

Methods

runOp :: ResizeSuper () -> orig -> Ref Dial -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (ResizeSuper ()) Adjuster orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Adjuster

Methods

runOp :: ResizeSuper () -> orig -> Ref Adjuster -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (ResizeSuper ()) MenuButton orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuButton

Methods

runOp :: ResizeSuper () -> orig -> Ref MenuButton -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (ResizeSuper ()) Choice orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Choice

Methods

runOp :: ResizeSuper () -> orig -> Ref Choice -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (ResizeSuper ()) SysMenuBar orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.SysMenuBar

Methods

runOp :: ResizeSuper () -> orig -> Ref SysMenuBar -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (ResizeSuper ()) MenuBar orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuBar

Methods

runOp :: ResizeSuper () -> orig -> Ref MenuBar -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (ResizeSuper ()) MenuPrim orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuPrim

Methods

runOp :: ResizeSuper () -> orig -> Ref MenuPrim -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (ResizeSuper ()) Slider orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Slider

Methods

runOp :: ResizeSuper () -> orig -> Ref Slider -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (ResizeSuper ()) Valuator orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Valuator

Methods

runOp :: ResizeSuper () -> orig -> Ref Valuator -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (ResizeSuper ()) RepeatButton orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.RepeatButton

Methods

runOp :: ResizeSuper () -> orig -> Ref RepeatButton -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (ResizeSuper ()) RoundButton orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.RoundButton

Methods

runOp :: ResizeSuper () -> orig -> Ref RoundButton -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (ResizeSuper ()) ReturnButton orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ReturnButton

Methods

runOp :: ResizeSuper () -> orig -> Ref ReturnButton -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (ResizeSuper ()) CheckButton orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.CheckButton

Methods

runOp :: ResizeSuper () -> orig -> Ref CheckButton -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (ResizeSuper ()) LightButton orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.LightButton

Methods

runOp :: ResizeSuper () -> orig -> Ref LightButton -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (ResizeSuper ()) Button orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Button

Methods

runOp :: ResizeSuper () -> orig -> Ref Button -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (ResizeSuper ()) DoubleWindow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.DoubleWindow

Methods

runOp :: ResizeSuper () -> orig -> Ref DoubleWindow -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (ResizeSuper ()) SingleWindow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.SingleWindow

Methods

runOp :: ResizeSuper () -> orig -> Ref SingleWindow -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (ResizeSuper ()) Window orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Window

Methods

runOp :: ResizeSuper () -> orig -> Ref Window -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (ResizeSuper ()) Group orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Group

Methods

runOp :: ResizeSuper () -> orig -> Ref Group -> impl Source #

impl ~ (Rectangle -> IO ()) => Op (ResizeSuper ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: ResizeSuper () -> orig -> Ref Widget -> impl Source #

impl ~ IO Position => Op (GetTopWindowOffset ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: GetTopWindowOffset () -> orig -> Ref Widget -> impl Source #

impl ~ IO (Maybe (Ref Window)) => Op (GetTopWindow ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: GetTopWindow () -> orig -> Ref Widget -> impl Source #

impl ~ IO (Maybe (Ref Window)) => Op (GetWindow ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: GetWindow () -> orig -> Ref Widget -> impl Source #

impl ~ (Maybe Width -> IO Size) => Op (MeasureLabel ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: MeasureLabel () -> orig -> Ref Widget -> impl Source #

impl ~ ([Damage] -> Rectangle -> IO ()) => Op (SetDamageInside ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: SetDamageInside () -> orig -> Ref Widget -> impl Source #

impl ~ ([Damage] -> IO ()) => Op (SetDamage ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: SetDamage () -> orig -> Ref Widget -> impl Source #

impl ~ IO () => Op (ClearDamage ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: ClearDamage () -> orig -> Ref Widget -> impl Source #

impl ~ ([Damage] -> IO ()) => Op (ClearDamageThenSet ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: ClearDamageThenSet () -> orig -> Ref Widget -> impl Source #

impl ~ IO [Damage] => Op (GetDamage ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: GetDamage () -> orig -> Ref Widget -> impl Source #

impl ~ IO () => Op (RedrawLabel ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: RedrawLabel () -> orig -> Ref Widget -> impl Source #

impl ~ IO () => Op (Redraw ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: Redraw () -> orig -> Ref Widget -> impl Source #

(Parent a Widget, impl ~ (Ref a -> IO Bool)) => Op (Inside ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: Inside () -> orig -> Ref Widget -> impl Source #

(Parent a Widget, impl ~ (Ref a -> IO Bool)) => Op (Contains ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: Contains () -> orig -> Ref Widget -> impl Source #

impl ~ IO Bool => Op (GetVisibleFocus ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: GetVisibleFocus () -> orig -> Ref Widget -> impl Source #

impl ~ (Bool -> IO ()) => Op (ModifyVisibleFocus ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: ModifyVisibleFocus () -> orig -> Ref Widget -> impl Source #

impl ~ IO () => Op (ClearVisibleFocus ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: ClearVisibleFocus () -> orig -> Ref Widget -> impl Source #

impl ~ IO () => Op (SetVisibleFocus ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: SetVisibleFocus () -> orig -> Ref Widget -> impl Source #

impl ~ IO (Either NoChange ()) => Op (TakeFocus ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: TakeFocus () -> orig -> Ref Widget -> impl Source #

impl ~ IO () => Op (ClearActive ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: ClearActive () -> orig -> Ref Widget -> impl Source #

impl ~ IO () => Op (SetActive ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: SetActive () -> orig -> Ref Widget -> impl Source #

impl ~ IO () => Op (ClearChanged ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: ClearChanged () -> orig -> Ref Widget -> impl Source #

impl ~ IO () => Op (SetChanged ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: SetChanged () -> orig -> Ref Widget -> impl Source #

impl ~ IO Bool => Op (Takesevents ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: Takesevents () -> orig -> Ref Widget -> impl Source #

impl ~ IO () => Op (ClearOutput ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: ClearOutput () -> orig -> Ref Widget -> impl Source #

impl ~ IO () => Op (SetOutput ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: SetOutput () -> orig -> Ref Widget -> impl Source #

impl ~ IO Int => Op (GetOutput ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: GetOutput () -> orig -> Ref Widget -> impl Source #

impl ~ IO () => Op (Deactivate ()) MenuItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuItem

Methods

runOp :: Deactivate () -> orig -> Ref MenuItem -> impl Source #

impl ~ IO () => Op (Deactivate ()) RepeatButton orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.RepeatButton

Methods

runOp :: Deactivate () -> orig -> Ref RepeatButton -> impl Source #

impl ~ IO () => Op (Deactivate ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: Deactivate () -> orig -> Ref Widget -> impl Source #

impl ~ IO () => Op (Activate ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: Activate () -> orig -> Ref TreeItem -> impl Source #

impl ~ IO () => Op (Activate ()) MenuItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuItem

Methods

runOp :: Activate () -> orig -> Ref MenuItem -> impl Source #

impl ~ IO () => Op (Activate ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: Activate () -> orig -> Ref Widget -> impl Source #

impl ~ IO Bool => Op (ActiveR ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: ActiveR () -> orig -> Ref Widget -> impl Source #

impl ~ IO Bool => Op (Active ()) MenuItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuItem

Methods

runOp :: Active () -> orig -> Ref MenuItem -> impl Source #

impl ~ IO Bool => Op (Active ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: Active () -> orig -> Ref Widget -> impl Source #

impl ~ IO () => Op (ClearVisible ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: ClearVisible () -> orig -> Ref Widget -> impl Source #

impl ~ IO () => Op (SetVisible ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: SetVisible () -> orig -> Ref Widget -> impl Source #

impl ~ IO () => Op (Hide ()) FileInput orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.FileInput

Methods

runOp :: Hide () -> orig -> Ref FileInput -> impl Source #

impl ~ IO () => Op (Hide ()) FileBrowser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.FileBrowser

Methods

runOp :: Hide () -> orig -> Ref FileBrowser -> impl Source #

impl ~ IO () => Op (Hide ()) ColorChooser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ColorChooser

Methods

runOp :: Hide () -> orig -> Ref ColorChooser -> impl Source #

impl ~ IO () => Op (Hide ()) Spinner orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Spinner

Methods

runOp :: Hide () -> orig -> Ref Spinner -> impl Source #

impl ~ IO () => Op (Hide ()) Tabs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tabs

Methods

runOp :: Hide () -> orig -> Ref Tabs -> impl Source #

impl ~ IO () => Op (Hide ()) Scrolled orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Scrolled

Methods

runOp :: Hide () -> orig -> Ref Scrolled -> impl Source #

impl ~ IO () => Op (Hide ()) Pack orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Pack

Methods

runOp :: Hide () -> orig -> Ref Pack -> impl Source #

impl ~ IO () => Op (Hide ()) Tile orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tile

Methods

runOp :: Hide () -> orig -> Ref Tile -> impl Source #

impl ~ IO () => Op (Hide ()) TextEditor orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextEditor

Methods

runOp :: Hide () -> orig -> Ref TextEditor -> impl Source #

impl ~ IO () => Op (Hide ()) TextDisplay orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextDisplay

Methods

runOp :: Hide () -> orig -> Ref TextDisplay -> impl Source #

impl ~ IO () => Op (Hide ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: Hide () -> orig -> Ref Tree -> impl Source #

impl ~ IO () => Op (Hide ()) Clock orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Clock

Methods

runOp :: Hide () -> orig -> Ref Clock -> impl Source #

impl ~ IO () => Op (Hide ()) Browser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Browser

Methods

runOp :: Hide () -> orig -> Ref Browser -> impl Source #

impl ~ IO () => Op (Hide ()) GlWindow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.GlWindow

Methods

runOp :: Hide () -> orig -> Ref GlWindow -> impl Source #

impl ~ IO () => Op (Hide ()) TableRow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TableRow

Methods

runOp :: Hide () -> orig -> Ref TableRow -> impl Source #

impl ~ IO () => Op (Hide ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: Hide () -> orig -> Ref Table -> impl Source #

impl ~ IO () => Op (Hide ()) Wizard orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Wizard

Methods

runOp :: Hide () -> orig -> Ref Wizard -> impl Source #

impl ~ IO () => Op (Hide ()) Positioner orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Positioner

Methods

runOp :: Hide () -> orig -> Ref Positioner -> impl Source #

impl ~ IO () => Op (Hide ()) Progress orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Progress

Methods

runOp :: Hide () -> orig -> Ref Progress -> impl Source #

impl ~ IO () => Op (Hide ()) ValueOutput orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ValueOutput

Methods

runOp :: Hide () -> orig -> Ref ValueOutput -> impl Source #

impl ~ IO () => Op (Hide ()) ValueInput orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ValueInput

Methods

runOp :: Hide () -> orig -> Ref ValueInput -> impl Source #

impl ~ IO () => Op (Hide ()) Output orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Output

Methods

runOp :: Hide () -> orig -> Ref Output -> impl Source #

impl ~ IO () => Op (Hide ()) Input orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Input

Methods

runOp :: Hide () -> orig -> Ref Input -> impl Source #

impl ~ IO () => Op (Hide ()) ValueSlider orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ValueSlider

Methods

runOp :: Hide () -> orig -> Ref ValueSlider -> impl Source #

impl ~ IO () => Op (Hide ()) Scrollbar orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Scrollbar

Methods

runOp :: Hide () -> orig -> Ref Scrollbar -> impl Source #

impl ~ IO () => Op (Hide ()) Counter orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Counter

Methods

runOp :: Hide () -> orig -> Ref Counter -> impl Source #

impl ~ IO () => Op (Hide ()) Roller orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Roller

Methods

runOp :: Hide () -> orig -> Ref Roller -> impl Source #

impl ~ IO () => Op (Hide ()) Dial orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Dial

Methods

runOp :: Hide () -> orig -> Ref Dial -> impl Source #

impl ~ IO () => Op (Hide ()) Adjuster orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Adjuster

Methods

runOp :: Hide () -> orig -> Ref Adjuster -> impl Source #

impl ~ IO () => Op (Hide ()) MenuButton orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuButton

Methods

runOp :: Hide () -> orig -> Ref MenuButton -> impl Source #

impl ~ IO () => Op (Hide ()) Choice orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Choice

Methods

runOp :: Hide () -> orig -> Ref Choice -> impl Source #

impl ~ IO () => Op (Hide ()) SysMenuBar orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.SysMenuBar

Methods

runOp :: Hide () -> orig -> Ref SysMenuBar -> impl Source #

impl ~ IO () => Op (Hide ()) MenuBar orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuBar

Methods

runOp :: Hide () -> orig -> Ref MenuBar -> impl Source #

impl ~ IO () => Op (Hide ()) MenuPrim orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuPrim

Methods

runOp :: Hide () -> orig -> Ref MenuPrim -> impl Source #

impl ~ IO () => Op (Hide ()) MenuItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuItem

Methods

runOp :: Hide () -> orig -> Ref MenuItem -> impl Source #

impl ~ IO () => Op (Hide ()) Slider orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Slider

Methods

runOp :: Hide () -> orig -> Ref Slider -> impl Source #

impl ~ IO () => Op (Hide ()) Valuator orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Valuator

Methods

runOp :: Hide () -> orig -> Ref Valuator -> impl Source #

impl ~ IO () => Op (Hide ()) RepeatButton orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.RepeatButton

Methods

runOp :: Hide () -> orig -> Ref RepeatButton -> impl Source #

impl ~ IO () => Op (Hide ()) RoundButton orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.RoundButton

Methods

runOp :: Hide () -> orig -> Ref RoundButton -> impl Source #

impl ~ IO () => Op (Hide ()) ReturnButton orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ReturnButton

Methods

runOp :: Hide () -> orig -> Ref ReturnButton -> impl Source #

impl ~ IO () => Op (Hide ()) CheckButton orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.CheckButton

Methods

runOp :: Hide () -> orig -> Ref CheckButton -> impl Source #

impl ~ IO () => Op (Hide ()) LightButton orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.LightButton

Methods

runOp :: Hide () -> orig -> Ref LightButton -> impl Source #

impl ~ IO () => Op (Hide ()) Button orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Button

Methods

runOp :: Hide () -> orig -> Ref Button -> impl Source #

impl ~ IO () => Op (Hide ()) OverlayWindow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.OverlayWindow

Methods

runOp :: Hide () -> orig -> Ref OverlayWindow -> impl Source #

impl ~ IO () => Op (Hide ()) DoubleWindow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.DoubleWindow

Methods

runOp :: Hide () -> orig -> Ref DoubleWindow -> impl Source #

impl ~ IO () => Op (Hide ()) SingleWindow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.SingleWindow

Methods

runOp :: Hide () -> orig -> Ref SingleWindow -> impl Source #

impl ~ IO () => Op (Hide ()) Window orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Window

Methods

runOp :: Hide () -> orig -> Ref Window -> impl Source #

impl ~ IO () => Op (Hide ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: Hide () -> orig -> Ref Widget -> impl Source #

impl ~ IO () => Op (HideSuper ()) SimpleTerminal orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.SimpleTerminal

Methods

runOp :: HideSuper () -> orig -> Ref SimpleTerminal -> impl Source #

impl ~ IO () => Op (HideSuper ()) FileInput orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.FileInput

Methods

runOp :: HideSuper () -> orig -> Ref FileInput -> impl Source #

impl ~ IO () => Op (HideSuper ()) FileBrowser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.FileBrowser

Methods

runOp :: HideSuper () -> orig -> Ref FileBrowser -> impl Source #

impl ~ IO () => Op (HideSuper ()) ColorChooser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ColorChooser

Methods

runOp :: HideSuper () -> orig -> Ref ColorChooser -> impl Source #

impl ~ IO () => Op (HideSuper ()) Spinner orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Spinner

Methods

runOp :: HideSuper () -> orig -> Ref Spinner -> impl Source #

impl ~ IO () => Op (HideSuper ()) Tabs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tabs

Methods

runOp :: HideSuper () -> orig -> Ref Tabs -> impl Source #

impl ~ IO () => Op (HideSuper ()) Scrolled orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Scrolled

Methods

runOp :: HideSuper () -> orig -> Ref Scrolled -> impl Source #

impl ~ IO () => Op (HideSuper ()) Pack orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Pack

Methods

runOp :: HideSuper () -> orig -> Ref Pack -> impl Source #

impl ~ IO () => Op (HideSuper ()) Tile orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tile

Methods

runOp :: HideSuper () -> orig -> Ref Tile -> impl Source #

impl ~ IO () => Op (HideSuper ()) TextEditor orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextEditor

Methods

runOp :: HideSuper () -> orig -> Ref TextEditor -> impl Source #

impl ~ IO () => Op (HideSuper ()) TextDisplay orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextDisplay

Methods

runOp :: HideSuper () -> orig -> Ref TextDisplay -> impl Source #

impl ~ IO () => Op (HideSuper ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: HideSuper () -> orig -> Ref Tree -> impl Source #

impl ~ IO () => Op (HideSuper ()) Clock orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Clock

Methods

runOp :: HideSuper () -> orig -> Ref Clock -> impl Source #

impl ~ IO () => Op (HideSuper ()) GlWindow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.GlWindow

Methods

runOp :: HideSuper () -> orig -> Ref GlWindow -> impl Source #

impl ~ IO () => Op (HideSuper ()) TableRow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TableRow

Methods

runOp :: HideSuper () -> orig -> Ref TableRow -> impl Source #

impl ~ IO () => Op (HideSuper ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: HideSuper () -> orig -> Ref Table -> impl Source #

impl ~ IO () => Op (HideSuper ()) Wizard orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Wizard

Methods

runOp :: HideSuper () -> orig -> Ref Wizard -> impl Source #

impl ~ IO () => Op (HideSuper ()) Positioner orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Positioner

Methods

runOp :: HideSuper () -> orig -> Ref Positioner -> impl Source #

impl ~ IO () => Op (HideSuper ()) Progress orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Progress

Methods

runOp :: HideSuper () -> orig -> Ref Progress -> impl Source #

impl ~ IO () => Op (HideSuper ()) ValueOutput orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ValueOutput

Methods

runOp :: HideSuper () -> orig -> Ref ValueOutput -> impl Source #

impl ~ IO () => Op (HideSuper ()) ValueInput orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ValueInput

Methods

runOp :: HideSuper () -> orig -> Ref ValueInput -> impl Source #

impl ~ IO () => Op (HideSuper ()) Output orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Output

Methods

runOp :: HideSuper () -> orig -> Ref Output -> impl Source #

impl ~ IO () => Op (HideSuper ()) Input orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Input

Methods

runOp :: HideSuper () -> orig -> Ref Input -> impl Source #

impl ~ IO () => Op (HideSuper ()) ValueSlider orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ValueSlider

Methods

runOp :: HideSuper () -> orig -> Ref ValueSlider -> impl Source #

impl ~ IO () => Op (HideSuper ()) Scrollbar orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Scrollbar

Methods

runOp :: HideSuper () -> orig -> Ref Scrollbar -> impl Source #

impl ~ IO () => Op (HideSuper ()) Counter orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Counter

Methods

runOp :: HideSuper () -> orig -> Ref Counter -> impl Source #

impl ~ IO () => Op (HideSuper ()) Roller orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Roller

Methods

runOp :: HideSuper () -> orig -> Ref Roller -> impl Source #

impl ~ IO () => Op (HideSuper ()) Dial orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Dial

Methods

runOp :: HideSuper () -> orig -> Ref Dial -> impl Source #

impl ~ IO () => Op (HideSuper ()) Adjuster orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Adjuster

Methods

runOp :: HideSuper () -> orig -> Ref Adjuster -> impl Source #

impl ~ IO () => Op (HideSuper ()) MenuButton orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuButton

Methods

runOp :: HideSuper () -> orig -> Ref MenuButton -> impl Source #

impl ~ IO () => Op (HideSuper ()) Choice orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Choice

Methods

runOp :: HideSuper () -> orig -> Ref Choice -> impl Source #

impl ~ IO () => Op (HideSuper ()) SysMenuBar orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.SysMenuBar

Methods

runOp :: HideSuper () -> orig -> Ref SysMenuBar -> impl Source #

impl ~ IO () => Op (HideSuper ()) MenuBar orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuBar

Methods

runOp :: HideSuper () -> orig -> Ref MenuBar -> impl Source #

impl ~ IO () => Op (HideSuper ()) MenuPrim orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuPrim

Methods

runOp :: HideSuper () -> orig -> Ref MenuPrim -> impl Source #

impl ~ IO () => Op (HideSuper ()) Slider orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Slider

Methods

runOp :: HideSuper () -> orig -> Ref Slider -> impl Source #

impl ~ IO () => Op (HideSuper ()) Valuator orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Valuator

Methods

runOp :: HideSuper () -> orig -> Ref Valuator -> impl Source #

impl ~ IO () => Op (HideSuper ()) RepeatButton orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.RepeatButton

Methods

runOp :: HideSuper () -> orig -> Ref RepeatButton -> impl Source #

impl ~ IO () => Op (HideSuper ()) RoundButton orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.RoundButton

Methods

runOp :: HideSuper () -> orig -> Ref RoundButton -> impl Source #

impl ~ IO () => Op (HideSuper ()) ReturnButton orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ReturnButton

Methods

runOp :: HideSuper () -> orig -> Ref ReturnButton -> impl Source #

impl ~ IO () => Op (HideSuper ()) CheckButton orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.CheckButton

Methods

runOp :: HideSuper () -> orig -> Ref CheckButton -> impl Source #

impl ~ IO () => Op (HideSuper ()) LightButton orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.LightButton

Methods

runOp :: HideSuper () -> orig -> Ref LightButton -> impl Source #

impl ~ IO () => Op (HideSuper ()) Button orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Button

Methods

runOp :: HideSuper () -> orig -> Ref Button -> impl Source #

impl ~ IO () => Op (HideSuper ()) DoubleWindow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.DoubleWindow

Methods

runOp :: HideSuper () -> orig -> Ref DoubleWindow -> impl Source #

impl ~ IO () => Op (HideSuper ()) SingleWindow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.SingleWindow

Methods

runOp :: HideSuper () -> orig -> Ref SingleWindow -> impl Source #

impl ~ IO () => Op (HideSuper ()) Window orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Window

Methods

runOp :: HideSuper () -> orig -> Ref Window -> impl Source #

impl ~ IO () => Op (HideSuper ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: HideSuper () -> orig -> Ref Widget -> impl Source #

impl ~ IO () => Op (ShowWidget ()) FileInput orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.FileInput

Methods

runOp :: ShowWidget () -> orig -> Ref FileInput -> impl Source #

impl ~ IO () => Op (ShowWidget ()) FileBrowser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.FileBrowser

Methods

runOp :: ShowWidget () -> orig -> Ref FileBrowser -> impl Source #

impl ~ IO () => Op (ShowWidget ()) ColorChooser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ColorChooser

Methods

runOp :: ShowWidget () -> orig -> Ref ColorChooser -> impl Source #

impl ~ IO () => Op (ShowWidget ()) Spinner orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Spinner

Methods

runOp :: ShowWidget () -> orig -> Ref Spinner -> impl Source #

impl ~ IO () => Op (ShowWidget ()) Tabs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tabs

Methods

runOp :: ShowWidget () -> orig -> Ref Tabs -> impl Source #

impl ~ IO () => Op (ShowWidget ()) Scrolled orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Scrolled

Methods

runOp :: ShowWidget () -> orig -> Ref Scrolled -> impl Source #

impl ~ IO () => Op (ShowWidget ()) Pack orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Pack

Methods

runOp :: ShowWidget () -> orig -> Ref Pack -> impl Source #

impl ~ IO () => Op (ShowWidget ()) Tile orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tile

Methods

runOp :: ShowWidget () -> orig -> Ref Tile -> impl Source #

impl ~ IO NativeFileChooserUserAction => Op (ShowWidget ()) NativeFileChooser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.NativeFileChooser

Methods

runOp :: ShowWidget () -> orig -> Ref NativeFileChooser -> impl Source #

impl ~ IO () => Op (ShowWidget ()) TextEditor orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextEditor

Methods

runOp :: ShowWidget () -> orig -> Ref TextEditor -> impl Source #

impl ~ IO () => Op (ShowWidget ()) TextDisplay orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextDisplay

Methods

runOp :: ShowWidget () -> orig -> Ref TextDisplay -> impl Source #

impl ~ IO () => Op (ShowWidget ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: ShowWidget () -> orig -> Ref Tree -> impl Source #

impl ~ IO () => Op (ShowWidget ()) Clock orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Clock

Methods

runOp :: ShowWidget () -> orig -> Ref Clock -> impl Source #

impl ~ IO () => Op (ShowWidget ()) Browser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Browser

Methods

runOp :: ShowWidget () -> orig -> Ref Browser -> impl Source #

impl ~ IO () => Op (ShowWidget ()) GlWindow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.GlWindow

Methods

runOp :: ShowWidget () -> orig -> Ref GlWindow -> impl Source #

impl ~ IO () => Op (ShowWidget ()) TableRow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TableRow

Methods

runOp :: ShowWidget () -> orig -> Ref TableRow -> impl Source #

impl ~ IO () => Op (ShowWidget ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: ShowWidget () -> orig -> Ref Table -> impl Source #

impl ~ IO () => Op (ShowWidget ()) Wizard orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Wizard

Methods

runOp :: ShowWidget () -> orig -> Ref Wizard -> impl Source #

impl ~ IO () => Op (ShowWidget ()) Positioner orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Positioner

Methods

runOp :: ShowWidget () -> orig -> Ref Positioner -> impl Source #

impl ~ IO () => Op (ShowWidget ()) Progress orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Progress

Methods

runOp :: ShowWidget () -> orig -> Ref Progress -> impl Source #

impl ~ IO () => Op (ShowWidget ()) ValueOutput orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ValueOutput

Methods

runOp :: ShowWidget () -> orig -> Ref ValueOutput -> impl Source #

impl ~ IO () => Op (ShowWidget ()) ValueInput orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ValueInput

Methods

runOp :: ShowWidget () -> orig -> Ref ValueInput -> impl Source #

impl ~ IO () => Op (ShowWidget ()) Output orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Output

Methods

runOp :: ShowWidget () -> orig -> Ref Output -> impl Source #

impl ~ IO () => Op (ShowWidget ()) Input orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Input

Methods

runOp :: ShowWidget () -> orig -> Ref Input -> impl Source #

impl ~ IO () => Op (ShowWidget ()) ValueSlider orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ValueSlider

Methods

runOp :: ShowWidget () -> orig -> Ref ValueSlider -> impl Source #

impl ~ IO () => Op (ShowWidget ()) Scrollbar orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Scrollbar

Methods

runOp :: ShowWidget () -> orig -> Ref Scrollbar -> impl Source #

impl ~ IO () => Op (ShowWidget ()) Counter orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Counter

Methods

runOp :: ShowWidget () -> orig -> Ref Counter -> impl Source #

impl ~ IO () => Op (ShowWidget ()) Roller orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Roller

Methods

runOp :: ShowWidget () -> orig -> Ref Roller -> impl Source #

impl ~ IO () => Op (ShowWidget ()) Dial orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Dial

Methods

runOp :: ShowWidget () -> orig -> Ref Dial -> impl Source #

impl ~ IO () => Op (ShowWidget ()) Adjuster orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Adjuster

Methods

runOp :: ShowWidget () -> orig -> Ref Adjuster -> impl Source #

impl ~ IO () => Op (ShowWidget ()) MenuButton orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuButton

Methods

runOp :: ShowWidget () -> orig -> Ref MenuButton -> impl Source #

impl ~ IO () => Op (ShowWidget ()) Choice orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Choice

Methods

runOp :: ShowWidget () -> orig -> Ref Choice -> impl Source #

impl ~ IO () => Op (ShowWidget ()) SysMenuBar orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.SysMenuBar

Methods

runOp :: ShowWidget () -> orig -> Ref SysMenuBar -> impl Source #

impl ~ IO () => Op (ShowWidget ()) MenuBar orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuBar

Methods

runOp :: ShowWidget () -> orig -> Ref MenuBar -> impl Source #

impl ~ IO () => Op (ShowWidget ()) MenuPrim orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuPrim

Methods

runOp :: ShowWidget () -> orig -> Ref MenuPrim -> impl Source #

impl ~ IO () => Op (ShowWidget ()) MenuItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuItem

Methods

runOp :: ShowWidget () -> orig -> Ref MenuItem -> impl Source #

impl ~ IO () => Op (ShowWidget ()) Slider orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Slider

Methods

runOp :: ShowWidget () -> orig -> Ref Slider -> impl Source #

impl ~ IO () => Op (ShowWidget ()) RepeatButton orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.RepeatButton

Methods

runOp :: ShowWidget () -> orig -> Ref RepeatButton -> impl Source #

impl ~ IO () => Op (ShowWidget ()) RoundButton orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.RoundButton

Methods

runOp :: ShowWidget () -> orig -> Ref RoundButton -> impl Source #

impl ~ IO () => Op (ShowWidget ()) ReturnButton orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ReturnButton

Methods

runOp :: ShowWidget () -> orig -> Ref ReturnButton -> impl Source #

impl ~ IO () => Op (ShowWidget ()) CheckButton orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.CheckButton

Methods

runOp :: ShowWidget () -> orig -> Ref CheckButton -> impl Source #

impl ~ IO () => Op (ShowWidget ()) LightButton orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.LightButton

Methods

runOp :: ShowWidget () -> orig -> Ref LightButton -> impl Source #

impl ~ IO () => Op (ShowWidget ()) Button orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Button

Methods

runOp :: ShowWidget () -> orig -> Ref Button -> impl Source #

impl ~ IO () => Op (ShowWidget ()) OverlayWindow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.OverlayWindow

Methods

runOp :: ShowWidget () -> orig -> Ref OverlayWindow -> impl Source #

impl ~ IO () => Op (ShowWidget ()) DoubleWindow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.DoubleWindow

Methods

runOp :: ShowWidget () -> orig -> Ref DoubleWindow -> impl Source #

impl ~ IO () => Op (ShowWidget ()) SingleWindow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.SingleWindow

Methods

runOp :: ShowWidget () -> orig -> Ref SingleWindow -> impl Source #

impl ~ IO () => Op (ShowWidget ()) Window orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Window

Methods

runOp :: ShowWidget () -> orig -> Ref Window -> impl Source #

impl ~ IO () => Op (ShowWidget ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: ShowWidget () -> orig -> Ref Widget -> impl Source #

impl ~ IO () => Op (ShowWidgetSuper ()) SimpleTerminal orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.SimpleTerminal

Methods

runOp :: ShowWidgetSuper () -> orig -> Ref SimpleTerminal -> impl Source #

impl ~ IO () => Op (ShowWidgetSuper ()) FileInput orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.FileInput

Methods

runOp :: ShowWidgetSuper () -> orig -> Ref FileInput -> impl Source #

impl ~ IO () => Op (ShowWidgetSuper ()) FileBrowser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.FileBrowser

Methods

runOp :: ShowWidgetSuper () -> orig -> Ref FileBrowser -> impl Source #

impl ~ IO () => Op (ShowWidgetSuper ()) ColorChooser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ColorChooser

Methods

runOp :: ShowWidgetSuper () -> orig -> Ref ColorChooser -> impl Source #

impl ~ IO () => Op (ShowWidgetSuper ()) Spinner orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Spinner

Methods

runOp :: ShowWidgetSuper () -> orig -> Ref Spinner -> impl Source #

impl ~ IO () => Op (ShowWidgetSuper ()) Tabs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tabs

Methods

runOp :: ShowWidgetSuper () -> orig -> Ref Tabs -> impl Source #

impl ~ IO () => Op (ShowWidgetSuper ()) Scrolled orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Scrolled

Methods

runOp :: ShowWidgetSuper () -> orig -> Ref Scrolled -> impl Source #

impl ~ IO () => Op (ShowWidgetSuper ()) Pack orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Pack

Methods

runOp :: ShowWidgetSuper () -> orig -> Ref Pack -> impl Source #

impl ~ IO () => Op (ShowWidgetSuper ()) Tile orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tile

Methods

runOp :: ShowWidgetSuper () -> orig -> Ref Tile -> impl Source #

impl ~ IO () => Op (ShowWidgetSuper ()) TextEditor orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextEditor

Methods

runOp :: ShowWidgetSuper () -> orig -> Ref TextEditor -> impl Source #

impl ~ IO () => Op (ShowWidgetSuper ()) TextDisplay orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextDisplay

Methods

runOp :: ShowWidgetSuper () -> orig -> Ref TextDisplay -> impl Source #

impl ~ IO () => Op (ShowWidgetSuper ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: ShowWidgetSuper () -> orig -> Ref Tree -> impl Source #

impl ~ IO () => Op (ShowWidgetSuper ()) Clock orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Clock

Methods

runOp :: ShowWidgetSuper () -> orig -> Ref Clock -> impl Source #

impl ~ IO () => Op (ShowWidgetSuper ()) GlWindow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.GlWindow

Methods

runOp :: ShowWidgetSuper () -> orig -> Ref GlWindow -> impl Source #

impl ~ IO () => Op (ShowWidgetSuper ()) TableRow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TableRow

Methods

runOp :: ShowWidgetSuper () -> orig -> Ref TableRow -> impl Source #

impl ~ IO () => Op (ShowWidgetSuper ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: ShowWidgetSuper () -> orig -> Ref Table -> impl Source #

impl ~ IO () => Op (ShowWidgetSuper ()) Wizard orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Wizard

Methods

runOp :: ShowWidgetSuper () -> orig -> Ref Wizard -> impl Source #

impl ~ IO () => Op (ShowWidgetSuper ()) Positioner orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Positioner

Methods

runOp :: ShowWidgetSuper () -> orig -> Ref Positioner -> impl Source #

impl ~ IO () => Op (ShowWidgetSuper ()) Progress orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Progress

Methods

runOp :: ShowWidgetSuper () -> orig -> Ref Progress -> impl Source #

impl ~ IO () => Op (ShowWidgetSuper ()) ValueOutput orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ValueOutput

Methods

runOp :: ShowWidgetSuper () -> orig -> Ref ValueOutput -> impl Source #

impl ~ IO () => Op (ShowWidgetSuper ()) ValueInput orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ValueInput

Methods

runOp :: ShowWidgetSuper () -> orig -> Ref ValueInput -> impl Source #

impl ~ IO () => Op (ShowWidgetSuper ()) Output orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Output

Methods

runOp :: ShowWidgetSuper () -> orig -> Ref Output -> impl Source #

impl ~ IO () => Op (ShowWidgetSuper ()) Input orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Input

Methods

runOp :: ShowWidgetSuper () -> orig -> Ref Input -> impl Source #

impl ~ IO () => Op (ShowWidgetSuper ()) ValueSlider orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ValueSlider

Methods

runOp :: ShowWidgetSuper () -> orig -> Ref ValueSlider -> impl Source #

impl ~ IO () => Op (ShowWidgetSuper ()) Scrollbar orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Scrollbar

Methods

runOp :: ShowWidgetSuper () -> orig -> Ref Scrollbar -> impl Source #

impl ~ IO () => Op (ShowWidgetSuper ()) Counter orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Counter

Methods

runOp :: ShowWidgetSuper () -> orig -> Ref Counter -> impl Source #

impl ~ IO () => Op (ShowWidgetSuper ()) Roller orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Roller

Methods

runOp :: ShowWidgetSuper () -> orig -> Ref Roller -> impl Source #

impl ~ IO () => Op (ShowWidgetSuper ()) Dial orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Dial

Methods

runOp :: ShowWidgetSuper () -> orig -> Ref Dial -> impl Source #

impl ~ IO () => Op (ShowWidgetSuper ()) Adjuster orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Adjuster

Methods

runOp :: ShowWidgetSuper () -> orig -> Ref Adjuster -> impl Source #

impl ~ IO () => Op (ShowWidgetSuper ()) MenuButton orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuButton

Methods

runOp :: ShowWidgetSuper () -> orig -> Ref MenuButton -> impl Source #

impl ~ IO () => Op (ShowWidgetSuper ()) Choice orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Choice

Methods

runOp :: ShowWidgetSuper () -> orig -> Ref Choice -> impl Source #

impl ~ IO () => Op (ShowWidgetSuper ()) SysMenuBar orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.SysMenuBar

Methods

runOp :: ShowWidgetSuper () -> orig -> Ref SysMenuBar -> impl Source #

impl ~ IO () => Op (ShowWidgetSuper ()) MenuBar orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuBar

Methods

runOp :: ShowWidgetSuper () -> orig -> Ref MenuBar -> impl Source #

impl ~ IO () => Op (ShowWidgetSuper ()) MenuPrim orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuPrim

Methods

runOp :: ShowWidgetSuper () -> orig -> Ref MenuPrim -> impl Source #

impl ~ IO () => Op (ShowWidgetSuper ()) Slider orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Slider

Methods

runOp :: ShowWidgetSuper () -> orig -> Ref Slider -> impl Source #

impl ~ IO () => Op (ShowWidgetSuper ()) RepeatButton orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.RepeatButton

Methods

runOp :: ShowWidgetSuper () -> orig -> Ref RepeatButton -> impl Source #

impl ~ IO () => Op (ShowWidgetSuper ()) RoundButton orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.RoundButton

Methods

runOp :: ShowWidgetSuper () -> orig -> Ref RoundButton -> impl Source #

impl ~ IO () => Op (ShowWidgetSuper ()) ReturnButton orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ReturnButton

Methods

runOp :: ShowWidgetSuper () -> orig -> Ref ReturnButton -> impl Source #

impl ~ IO () => Op (ShowWidgetSuper ()) CheckButton orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.CheckButton

Methods

runOp :: ShowWidgetSuper () -> orig -> Ref CheckButton -> impl Source #

impl ~ IO () => Op (ShowWidgetSuper ()) LightButton orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.LightButton

Methods

runOp :: ShowWidgetSuper () -> orig -> Ref LightButton -> impl Source #

impl ~ IO () => Op (ShowWidgetSuper ()) Button orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Button

Methods

runOp :: ShowWidgetSuper () -> orig -> Ref Button -> impl Source #

impl ~ IO () => Op (ShowWidgetSuper ()) DoubleWindow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.DoubleWindow

Methods

runOp :: ShowWidgetSuper () -> orig -> Ref DoubleWindow -> impl Source #

impl ~ IO () => Op (ShowWidgetSuper ()) SingleWindow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.SingleWindow

Methods

runOp :: ShowWidgetSuper () -> orig -> Ref SingleWindow -> impl Source #

impl ~ IO () => Op (ShowWidgetSuper ()) Window orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Window

Methods

runOp :: ShowWidgetSuper () -> orig -> Ref Window -> impl Source #

impl ~ IO () => Op (ShowWidgetSuper ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: ShowWidgetSuper () -> orig -> Ref Widget -> impl Source #

impl ~ IO Bool => Op (GetVisibleR ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: GetVisibleR () -> orig -> Ref Widget -> impl Source #

impl ~ IO Bool => Op (GetVisible ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: GetVisible () -> orig -> Ref Widget -> impl Source #

impl ~ ([When] -> IO ()) => Op (SetWhen ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: SetWhen () -> orig -> Ref Widget -> impl Source #

impl ~ IO [When] => Op (GetWhen ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: GetWhen () -> orig -> Ref Widget -> impl Source #

impl ~ (Text -> IO ()) => Op (SetTooltip ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: SetTooltip () -> orig -> Ref Widget -> impl Source #

impl ~ (Text -> IO ()) => Op (CopyTooltip ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: CopyTooltip () -> orig -> Ref Widget -> impl Source #

impl ~ IO Text => Op (GetTooltip ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: GetTooltip () -> orig -> Ref Widget -> impl Source #

(Parent a Image, impl ~ (Maybe (Ref a) -> IO ())) => Op (SetDeimage ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: SetDeimage () -> orig -> Ref Widget -> impl Source #

impl ~ IO (Maybe (Ref Image)) => Op (GetDeimage ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: GetDeimage () -> orig -> Ref Widget -> impl Source #

(Parent a Image, impl ~ (Maybe (Ref a) -> IO ())) => Op (SetImage ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: SetImage () -> orig -> Ref Widget -> impl Source #

impl ~ IO (Maybe (Ref Image)) => Op (GetImage ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: GetImage () -> orig -> Ref Widget -> impl Source #

impl ~ (FontSize -> IO ()) => Op (SetLabelsize ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: SetLabelsize () -> orig -> Ref TreeItem -> impl Source #

impl ~ (FontSize -> IO ()) => Op (SetLabelsize ()) TreePrefs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreePrefs

Methods

runOp :: SetLabelsize () -> orig -> Ref TreePrefs -> impl Source #

impl ~ (FontSize -> IO ()) => Op (SetLabelsize ()) MenuItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuItem

Methods

runOp :: SetLabelsize () -> orig -> Ref MenuItem -> impl Source #

impl ~ (FontSize -> IO ()) => Op (SetLabelsize ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: SetLabelsize () -> orig -> Ref Widget -> impl Source #

impl ~ IO FontSize => Op (GetLabelsize ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: GetLabelsize () -> orig -> Ref TreeItem -> impl Source #

impl ~ IO FontSize => Op (GetLabelsize ()) TreePrefs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreePrefs

Methods

runOp :: GetLabelsize () -> orig -> Ref TreePrefs -> impl Source #

impl ~ IO FontSize => Op (GetLabelsize ()) MenuItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuItem

Methods

runOp :: GetLabelsize () -> orig -> Ref MenuItem -> impl Source #

impl ~ IO FontSize => Op (GetLabelsize ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: GetLabelsize () -> orig -> Ref Widget -> impl Source #

impl ~ (Font -> IO ()) => Op (SetLabelfont ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: SetLabelfont () -> orig -> Ref TreeItem -> impl Source #

impl ~ (Font -> IO ()) => Op (SetLabelfont ()) TreePrefs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreePrefs

Methods

runOp :: SetLabelfont () -> orig -> Ref TreePrefs -> impl Source #

impl ~ (Font -> IO ()) => Op (SetLabelfont ()) MenuItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuItem

Methods

runOp :: SetLabelfont () -> orig -> Ref MenuItem -> impl Source #

impl ~ (Font -> IO ()) => Op (SetLabelfont ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: SetLabelfont () -> orig -> Ref Widget -> impl Source #

impl ~ IO Font => Op (GetLabelfont ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: GetLabelfont () -> orig -> Ref TreeItem -> impl Source #

impl ~ IO Font => Op (GetLabelfont ()) TreePrefs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreePrefs

Methods

runOp :: GetLabelfont () -> orig -> Ref TreePrefs -> impl Source #

impl ~ IO Font => Op (GetLabelfont ()) MenuItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuItem

Methods

runOp :: GetLabelfont () -> orig -> Ref MenuItem -> impl Source #

impl ~ IO Font => Op (GetLabelfont ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: GetLabelfont () -> orig -> Ref Widget -> impl Source #

impl ~ (Color -> IO ()) => Op (SetLabelcolor ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: SetLabelcolor () -> orig -> Ref TreeItem -> impl Source #

impl ~ (Color -> IO ()) => Op (SetLabelcolor ()) MenuItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuItem

Methods

runOp :: SetLabelcolor () -> orig -> Ref MenuItem -> impl Source #

impl ~ (Color -> IO ()) => Op (SetLabelcolor ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: SetLabelcolor () -> orig -> Ref Widget -> impl Source #

impl ~ IO Color => Op (GetLabelcolor ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: GetLabelcolor () -> orig -> Ref TreeItem -> impl Source #

impl ~ IO Color => Op (GetLabelcolor ()) MenuItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuItem

Methods

runOp :: GetLabelcolor () -> orig -> Ref MenuItem -> impl Source #

impl ~ IO Color => Op (GetLabelcolor ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: GetLabelcolor () -> orig -> Ref Widget -> impl Source #

impl ~ (Labeltype -> IO ()) => Op (SetLabeltype ()) MenuItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuItem

Methods

runOp :: SetLabeltype () -> orig -> Ref MenuItem -> impl Source #

impl ~ (Labeltype -> ResolveImageLabelConflict -> IO ()) => Op (SetLabeltype ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: SetLabeltype () -> orig -> Ref Widget -> impl Source #

impl ~ IO Labeltype => Op (GetLabeltype ()) MenuItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuItem

Methods

runOp :: GetLabeltype () -> orig -> Ref MenuItem -> impl Source #

impl ~ IO Labeltype => Op (GetLabeltype ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: GetLabeltype () -> orig -> Ref Widget -> impl Source #

impl ~ (Text -> IO ()) => Op (SetLabel ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: SetLabel () -> orig -> Ref TreeItem -> impl Source #

impl ~ (Text -> IO ()) => Op (SetLabel ()) MenuItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuItem

Methods

runOp :: SetLabel () -> orig -> Ref MenuItem -> impl Source #

impl ~ (Text -> IO ()) => Op (SetLabel ()) Window orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Window

Methods

runOp :: SetLabel () -> orig -> Ref Window -> impl Source #

impl ~ (Text -> IO ()) => Op (SetLabel ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: SetLabel () -> orig -> Ref Widget -> impl Source #

impl ~ (Text -> IO ()) => Op (CopyLabel ()) Window orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Window

Methods

runOp :: CopyLabel () -> orig -> Ref Window -> impl Source #

impl ~ IO Text => Op (GetLabel ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: GetLabel () -> orig -> Ref TreeItem -> impl Source #

impl ~ IO Text => Op (GetLabel ()) MenuItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuItem

Methods

runOp :: GetLabel () -> orig -> Ref MenuItem -> impl Source #

impl ~ IO Text => Op (GetLabel ()) Window orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Window

Methods

runOp :: GetLabel () -> orig -> Ref Window -> impl Source #

impl ~ IO Text => Op (GetLabel ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: GetLabel () -> orig -> Ref Widget -> impl Source #

impl ~ (Color -> IO ()) => Op (SetSelectionColor ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: SetSelectionColor () -> orig -> Ref Widget -> impl Source #

impl ~ IO Color => Op (GetSelectionColor ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: GetSelectionColor () -> orig -> Ref Widget -> impl Source #

impl ~ (Color -> Color -> IO ()) => Op (SetColorWithBgSel ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: SetColorWithBgSel () -> orig -> Ref Widget -> impl Source #

impl ~ (Color -> IO ()) => Op (SetColor ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: SetColor () -> orig -> Ref Widget -> impl Source #

impl ~ IO Color => Op (GetColor ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: GetColor () -> orig -> Ref Widget -> impl Source #

impl ~ (Boxtype -> IO ()) => Op (SetBox ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: SetBox () -> orig -> Ref Widget -> impl Source #

impl ~ IO Boxtype => Op (GetBox ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: GetBox () -> orig -> Ref Widget -> impl Source #

impl ~ IO Alignments => Op (GetAlign ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: GetAlign () -> orig -> Ref Widget -> impl Source #

impl ~ (Alignments -> IO ()) => Op (SetAlign ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: SetAlign () -> orig -> Ref Widget -> impl Source #

(Match obj ~ FindOp orig orig (GetX ()), Match obj ~ FindOp orig orig (GetY ()), Match obj ~ FindOp orig orig (GetW ()), Match obj ~ FindOp orig orig (GetH ()), Op (GetX ()) obj orig (IO X), Op (GetY ()) obj orig (IO Y), Op (GetW ()) obj orig (IO Width), Op (GetH ()) obj orig (IO Height), impl ~ IO Rectangle) => Op (GetRectangle ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: GetRectangle () -> orig -> Ref Widget -> impl Source #

impl ~ IO Int => Op (GetH ()) RGBImage orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.RGBImage

Methods

runOp :: GetH () -> orig -> Ref RGBImage -> impl Source #

impl ~ IO Int => Op (GetH ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: GetH () -> orig -> Ref TreeItem -> impl Source #

impl ~ IO Int => Op (GetH ()) Pixmap orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Pixmap

Methods

runOp :: GetH () -> orig -> Ref Pixmap -> impl Source #

impl ~ IO Int => Op (GetH ()) Bitmap orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Bitmap

Methods

runOp :: GetH () -> orig -> Ref Bitmap -> impl Source #

impl ~ IO Height => Op (GetH ()) Image orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Image

Methods

runOp :: GetH () -> orig -> Ref Image -> impl Source #

impl ~ IO Height => Op (GetH ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: GetH () -> orig -> Ref Widget -> impl Source #

impl ~ IO Int => Op (GetW ()) RGBImage orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.RGBImage

Methods

runOp :: GetW () -> orig -> Ref RGBImage -> impl Source #

impl ~ IO Int => Op (GetW ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: GetW () -> orig -> Ref TreeItem -> impl Source #

impl ~ IO Int => Op (GetW ()) Pixmap orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Pixmap

Methods

runOp :: GetW () -> orig -> Ref Pixmap -> impl Source #

impl ~ IO Int => Op (GetW ()) Bitmap orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Bitmap

Methods

runOp :: GetW () -> orig -> Ref Bitmap -> impl Source #

impl ~ IO Width => Op (GetW ()) Image orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Image

Methods

runOp :: GetW () -> orig -> Ref Image -> impl Source #

impl ~ IO Width => Op (GetW ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: GetW () -> orig -> Ref Widget -> impl Source #

impl ~ IO Int => Op (GetY ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: GetY () -> orig -> Ref TreeItem -> impl Source #

impl ~ IO Y => Op (GetY ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: GetY () -> orig -> Ref Widget -> impl Source #

impl ~ IO Int => Op (GetX ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: GetX () -> orig -> Ref TreeItem -> impl Source #

impl ~ IO X => Op (GetX ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: GetX () -> orig -> Ref Widget -> impl Source #

impl ~ (Maybe (Rectangle, Alignments) -> IO ()) => Op (DrawLabel ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: DrawLabel () -> orig -> Ref Widget -> impl Source #

impl ~ (SpinnerType -> IO ()) => Op (SetType ()) Spinner orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Spinner

Methods

runOp :: SetType () -> orig -> Ref Spinner -> impl Source #

impl ~ (ScrollbarMode -> IO ()) => Op (SetType ()) Scrolled orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Scrolled

Methods

runOp :: SetType () -> orig -> Ref Scrolled -> impl Source #

impl ~ (PackType -> IO ()) => Op (SetType ()) Pack orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Pack

Methods

runOp :: SetType () -> orig -> Ref Pack -> impl Source #

impl ~ (NativeFileChooserType -> IO ()) => Op (SetType ()) NativeFileChooser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.NativeFileChooser

Methods

runOp :: SetType () -> orig -> Ref NativeFileChooser -> impl Source #

impl ~ (ClockType -> IO ()) => Op (SetType ()) Clock orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Clock

Methods

runOp :: SetType () -> orig -> Ref Clock -> impl Source #

impl ~ (BrowserType -> IO ()) => Op (SetType ()) Browser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Browser

Methods

runOp :: SetType () -> orig -> Ref Browser -> impl Source #

impl ~ (TableRowSelectMode -> IO ()) => Op (SetType ()) TableRow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TableRow

Methods

runOp :: SetType () -> orig -> Ref TableRow -> impl Source #

impl ~ (FlOutputType -> IO ()) => Op (SetType ()) Output orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Output

Methods

runOp :: SetType () -> orig -> Ref Output -> impl Source #

impl ~ (ScrollbarType -> IO ()) => Op (SetType ()) Scrollbar orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Scrollbar

Methods

runOp :: SetType () -> orig -> Ref Scrollbar -> impl Source #

impl ~ (CounterType -> IO ()) => Op (SetType ()) Counter orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Counter

Methods

runOp :: SetType () -> orig -> Ref Counter -> impl Source #

impl ~ (DialType -> IO ()) => Op (SetType ()) Dial orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Dial

Methods

runOp :: SetType () -> orig -> Ref Dial -> impl Source #

impl ~ (SliderType -> IO ()) => Op (SetType ()) Slider orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Slider

Methods

runOp :: SetType () -> orig -> Ref Slider -> impl Source #

impl ~ (ValuatorType -> IO ()) => Op (SetType ()) Valuator orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Valuator

Methods

runOp :: SetType () -> orig -> Ref Valuator -> impl Source #

impl ~ (ButtonType -> IO ()) => Op (SetType ()) Button orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Button

Methods

runOp :: SetType () -> orig -> Ref Button -> impl Source #

impl ~ (WindowType -> IO ()) => Op (SetType ()) Window orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Window

Methods

runOp :: SetType () -> orig -> Ref Window -> impl Source #

impl ~ (Word8 -> IO ()) => Op (SetType ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: SetType () -> orig -> Ref Widget -> impl Source #

impl ~ IO SpinnerType => Op (GetType_ ()) Spinner orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Spinner

Methods

runOp :: GetType_ () -> orig -> Ref Spinner -> impl Source #

impl ~ IO ScrollbarMode => Op (GetType_ ()) Scrolled orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Scrolled

Methods

runOp :: GetType_ () -> orig -> Ref Scrolled -> impl Source #

impl ~ IO PackType => Op (GetType_ ()) Pack orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Pack

Methods

runOp :: GetType_ () -> orig -> Ref Pack -> impl Source #

impl ~ IO NativeFileChooserType => Op (GetType_ ()) NativeFileChooser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.NativeFileChooser

Methods

runOp :: GetType_ () -> orig -> Ref NativeFileChooser -> impl Source #

impl ~ IO ClockType => Op (GetType_ ()) Clock orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Clock

Methods

runOp :: GetType_ () -> orig -> Ref Clock -> impl Source #

impl ~ IO BrowserType => Op (GetType_ ()) Browser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Browser

Methods

runOp :: GetType_ () -> orig -> Ref Browser -> impl Source #

impl ~ IO TableRowSelectMode => Op (GetType_ ()) TableRow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TableRow

Methods

runOp :: GetType_ () -> orig -> Ref TableRow -> impl Source #

impl ~ IO ScrollbarType => Op (GetType_ ()) Scrollbar orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Scrollbar

Methods

runOp :: GetType_ () -> orig -> Ref Scrollbar -> impl Source #

impl ~ IO CounterType => Op (GetType_ ()) Counter orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Counter

Methods

runOp :: GetType_ () -> orig -> Ref Counter -> impl Source #

impl ~ IO DialType => Op (GetType_ ()) Dial orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Dial

Methods

runOp :: GetType_ () -> orig -> Ref Dial -> impl Source #

impl ~ IO SliderType => Op (GetType_ ()) Slider orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Slider

Methods

runOp :: GetType_ () -> orig -> Ref Slider -> impl Source #

impl ~ IO ValuatorType => Op (GetType_ ()) Valuator orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Valuator

Methods

runOp :: GetType_ () -> orig -> Ref Valuator -> impl Source #

impl ~ IO ButtonType => Op (GetType_ ()) Button orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Button

Methods

runOp :: GetType_ () -> orig -> Ref Button -> impl Source #

impl ~ IO WindowType => Op (GetType_ ()) Window orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Window

Methods

runOp :: GetType_ () -> orig -> Ref Window -> impl Source #

impl ~ IO Word8 => Op (GetType_ ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: GetType_ () -> orig -> Ref Widget -> impl Source #

(Parent a TreeItem, impl ~ (Maybe (Ref a) -> IO ())) => Op (SetParent ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: SetParent () -> orig -> Ref TreeItem -> impl Source #

(Parent a Group, impl ~ (Maybe (Ref a) -> IO ())) => Op (SetParent ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: SetParent () -> orig -> Ref Widget -> impl Source #

impl ~ IO (Maybe (Ref TreeItem)) => Op (GetParent ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: GetParent () -> orig -> Ref TreeItem -> impl Source #

impl ~ IO (Maybe (Ref Group)) => Op (GetParent ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: GetParent () -> orig -> Ref Widget -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (Handle ()) FileInput orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.FileInput

Methods

runOp :: Handle () -> orig -> Ref FileInput -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (Handle ()) FileBrowser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.FileBrowser

Methods

runOp :: Handle () -> orig -> Ref FileBrowser -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (Handle ()) ColorChooser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ColorChooser

Methods

runOp :: Handle () -> orig -> Ref ColorChooser -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (Handle ()) Spinner orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Spinner

Methods

runOp :: Handle () -> orig -> Ref Spinner -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (Handle ()) Tabs orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tabs

Methods

runOp :: Handle () -> orig -> Ref Tabs -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (Handle ()) Scrolled orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Scrolled

Methods

runOp :: Handle () -> orig -> Ref Scrolled -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (Handle ()) Pack orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Pack

Methods

runOp :: Handle () -> orig -> Ref Pack -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (Handle ()) Tile orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tile

Methods

runOp :: Handle () -> orig -> Ref Tile -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (Handle ()) TextEditor orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextEditor

Methods

runOp :: Handle () -> orig -> Ref TextEditor -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (Handle ()) TextDisplay orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextDisplay

Methods

runOp :: Handle () -> orig -> Ref TextDisplay -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (Handle ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: Handle () -> orig -> Ref Tree -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (Handle ()) Clock orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Clock

Methods

runOp :: Handle () -> orig -> Ref Clock -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (Handle ()) Browser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Browser

Methods

runOp :: Handle () -> orig -> Ref Browser -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (Handle ()) Box orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Box

Methods

runOp :: Handle () -> orig -> Ref Box -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (Handle ()) GlWindow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.GlWindow

Methods

runOp :: Handle () -> orig -> Ref GlWindow -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (Handle ()) TableRow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TableRow

Methods

runOp :: Handle () -> orig -> Ref TableRow -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (Handle ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: Handle () -> orig -> Ref Table -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (Handle ()) Wizard orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Wizard

Methods

runOp :: Handle () -> orig -> Ref Wizard -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (Handle ()) Positioner orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Positioner

Methods

runOp :: Handle () -> orig -> Ref Positioner -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (Handle ()) Progress orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Progress

Methods

runOp :: Handle () -> orig -> Ref Progress -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (Handle ()) ValueOutput orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ValueOutput

Methods

runOp :: Handle () -> orig -> Ref ValueOutput -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (Handle ()) ValueInput orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ValueInput

Methods

runOp :: Handle () -> orig -> Ref ValueInput -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (Handle ()) Output orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Output

Methods

runOp :: Handle () -> orig -> Ref Output -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (Handle ()) Input orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Input

Methods

runOp :: Handle () -> orig -> Ref Input -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (Handle ()) ValueSlider orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ValueSlider

Methods

runOp :: Handle () -> orig -> Ref ValueSlider -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (Handle ()) Scrollbar orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Scrollbar

Methods

runOp :: Handle () -> orig -> Ref Scrollbar -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (Handle ()) Counter orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Counter

Methods

runOp :: Handle () -> orig -> Ref Counter -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (Handle ()) Roller orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Roller

Methods

runOp :: Handle () -> orig -> Ref Roller -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (Handle ()) Dial orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Dial

Methods

runOp :: Handle () -> orig -> Ref Dial -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (Handle ()) Adjuster orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Adjuster

Methods

runOp :: Handle () -> orig -> Ref Adjuster -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (Handle ()) MenuButton orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuButton

Methods

runOp :: Handle () -> orig -> Ref MenuButton -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (Handle ()) Choice orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Choice

Methods

runOp :: Handle () -> orig -> Ref Choice -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (Handle ()) SysMenuBar orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.SysMenuBar

Methods

runOp :: Handle () -> orig -> Ref SysMenuBar -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (Handle ()) MenuBar orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuBar

Methods

runOp :: Handle () -> orig -> Ref MenuBar -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (Handle ()) MenuPrim orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuPrim

Methods

runOp :: Handle () -> orig -> Ref MenuPrim -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (Handle ()) Slider orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Slider

Methods

runOp :: Handle () -> orig -> Ref Slider -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (Handle ()) Valuator orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Valuator

Methods

runOp :: Handle () -> orig -> Ref Valuator -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (Handle ()) RepeatButton orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.RepeatButton

Methods

runOp :: Handle () -> orig -> Ref RepeatButton -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (Handle ()) RoundButton orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.RoundButton

Methods

runOp :: Handle () -> orig -> Ref RoundButton -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (Handle ()) ReturnButton orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ReturnButton

Methods

runOp :: Handle () -> orig -> Ref ReturnButton -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (Handle ()) CheckButton orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.CheckButton

Methods

runOp :: Handle () -> orig -> Ref CheckButton -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (Handle ()) LightButton orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.LightButton

Methods

runOp :: Handle () -> orig -> Ref LightButton -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (Handle ()) Button orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Button

Methods

runOp :: Handle () -> orig -> Ref Button -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (Handle ()) DoubleWindow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.DoubleWindow

Methods

runOp :: Handle () -> orig -> Ref DoubleWindow -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (Handle ()) SingleWindow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.SingleWindow

Methods

runOp :: Handle () -> orig -> Ref SingleWindow -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (Handle ()) Window orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Window

Methods

runOp :: Handle () -> orig -> Ref Window -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (Handle ()) Group orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Group

Methods

runOp :: Handle () -> orig -> Ref Group -> impl Source #

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (Handle ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: Handle () -> orig -> Ref Widget -> impl Source #

impl ~ IO () => Op (Destroy ()) SVGImage orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.SVGImage

Methods

runOp :: Destroy () -> orig -> Ref SVGImage -> impl Source #

impl ~ IO () => Op (Destroy ()) RGBImage orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.RGBImage

Methods

runOp :: Destroy () -> orig -> Ref RGBImage -> impl Source #

impl ~ IO () => Op (Destroy ()) NativeFileChooser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.NativeFileChooser

Methods

runOp :: Destroy () -> orig -> Ref NativeFileChooser -> impl Source #

impl ~ IO () => Op (Destroy ()) TextEditor orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextEditor

Methods

runOp :: Destroy () -> orig -> Ref TextEditor -> impl Source #

impl ~ IO () => Op (Destroy ()) TextDisplay orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextDisplay

Methods

runOp :: Destroy () -> orig -> Ref TextDisplay -> impl Source #

impl ~ IO () => Op (Destroy ()) TextBuffer orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TextBuffer

Methods

runOp :: Destroy () -> orig -> Ref TextBuffer -> impl Source #

impl ~ IO () => Op (Destroy ()) Tree orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Tree

Methods

runOp :: Destroy () -> orig -> Ref Tree -> impl Source #

impl ~ IO () => Op (Destroy ()) TreeItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TreeItem

Methods

runOp :: Destroy () -> orig -> Ref TreeItem -> impl Source #

impl ~ IO () => Op (Destroy ()) Browser orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Browser

Methods

runOp :: Destroy () -> orig -> Ref Browser -> impl Source #

impl ~ IO () => Op (Destroy ()) GlWindow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.GlWindow

Methods

runOp :: Destroy () -> orig -> Ref GlWindow -> impl Source #

impl ~ IO () => Op (Destroy ()) TableRow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.TableRow

Methods

runOp :: Destroy () -> orig -> Ref TableRow -> impl Source #

impl ~ IO () => Op (Destroy ()) Table orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Table

Methods

runOp :: Destroy () -> orig -> Ref Table -> impl Source #

impl ~ IO () => Op (Destroy ()) Wizard orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Wizard

Methods

runOp :: Destroy () -> orig -> Ref Wizard -> impl Source #

impl ~ IO () => Op (Destroy ()) Positioner orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Positioner

Methods

runOp :: Destroy () -> orig -> Ref Positioner -> impl Source #

impl ~ IO () => Op (Destroy ()) Progress orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Progress

Methods

runOp :: Destroy () -> orig -> Ref Progress -> impl Source #

impl ~ IO () => Op (Destroy ()) ValueOutput orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ValueOutput

Methods

runOp :: Destroy () -> orig -> Ref ValueOutput -> impl Source #

impl ~ IO () => Op (Destroy ()) ValueInput orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ValueInput

Methods

runOp :: Destroy () -> orig -> Ref ValueInput -> impl Source #

impl ~ IO () => Op (Destroy ()) Input orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Input

Methods

runOp :: Destroy () -> orig -> Ref Input -> impl Source #

impl ~ IO () => Op (Destroy ()) ValueSlider orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ValueSlider

Methods

runOp :: Destroy () -> orig -> Ref ValueSlider -> impl Source #

impl ~ IO () => Op (Destroy ()) Scrollbar orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Scrollbar

Methods

runOp :: Destroy () -> orig -> Ref Scrollbar -> impl Source #

impl ~ IO () => Op (Destroy ()) Counter orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Counter

Methods

runOp :: Destroy () -> orig -> Ref Counter -> impl Source #

impl ~ IO () => Op (Destroy ()) Roller orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Roller

Methods

runOp :: Destroy () -> orig -> Ref Roller -> impl Source #

impl ~ IO () => Op (Destroy ()) Dial orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Dial

Methods

runOp :: Destroy () -> orig -> Ref Dial -> impl Source #

impl ~ IO () => Op (Destroy ()) Adjuster orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Adjuster

Methods

runOp :: Destroy () -> orig -> Ref Adjuster -> impl Source #

impl ~ IO () => Op (Destroy ()) ImageSurface orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ImageSurface

Methods

runOp :: Destroy () -> orig -> Ref ImageSurface -> impl Source #

impl ~ IO () => Op (Destroy ()) CopySurface orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.CopySurface

Methods

runOp :: Destroy () -> orig -> Ref CopySurface -> impl Source #

impl ~ IO () => Op (Destroy ()) Pixmap orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Pixmap

Methods

runOp :: Destroy () -> orig -> Ref Pixmap -> impl Source #

impl ~ IO () => Op (Destroy ()) Bitmap orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Bitmap

Methods

runOp :: Destroy () -> orig -> Ref Bitmap -> impl Source #

impl ~ IO () => Op (Destroy ()) Image orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Image

Methods

runOp :: Destroy () -> orig -> Ref Image -> impl Source #

impl ~ IO () => Op (Destroy ()) MenuButton orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuButton

Methods

runOp :: Destroy () -> orig -> Ref MenuButton -> impl Source #

impl ~ IO () => Op (Destroy ()) Choice orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Choice

Methods

runOp :: Destroy () -> orig -> Ref Choice -> impl Source #

impl ~ IO () => Op (Destroy ()) SysMenuBar orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.SysMenuBar

Methods

runOp :: Destroy () -> orig -> Ref SysMenuBar -> impl Source #

impl ~ IO () => Op (Destroy ()) MenuBar orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuBar

Methods

runOp :: Destroy () -> orig -> Ref MenuBar -> impl Source #

impl ~ IO () => Op (Destroy ()) MenuPrim orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuPrim

Methods

runOp :: Destroy () -> orig -> Ref MenuPrim -> impl Source #

impl ~ IO () => Op (Destroy ()) MenuItem orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.MenuItem

Methods

runOp :: Destroy () -> orig -> Ref MenuItem -> impl Source #

impl ~ IO () => Op (Destroy ()) Slider orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Slider

Methods

runOp :: Destroy () -> orig -> Ref Slider -> impl Source #

impl ~ IO () => Op (Destroy ()) Valuator orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Valuator

Methods

runOp :: Destroy () -> orig -> Ref Valuator -> impl Source #

impl ~ IO () => Op (Destroy ()) ToggleButton orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ToggleButton

Methods

runOp :: Destroy () -> orig -> Ref ToggleButton -> impl Source #

impl ~ IO () => Op (Destroy ()) RepeatButton orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.RepeatButton

Methods

runOp :: Destroy () -> orig -> Ref RepeatButton -> impl Source #

impl ~ IO () => Op (Destroy ()) RoundButton orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.RoundButton

Methods

runOp :: Destroy () -> orig -> Ref RoundButton -> impl Source #

impl ~ IO () => Op (Destroy ()) ReturnButton orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.ReturnButton

Methods

runOp :: Destroy () -> orig -> Ref ReturnButton -> impl Source #

impl ~ IO () => Op (Destroy ()) CheckButton orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.CheckButton

Methods

runOp :: Destroy () -> orig -> Ref CheckButton -> impl Source #

impl ~ IO () => Op (Destroy ()) LightButton orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.LightButton

Methods

runOp :: Destroy () -> orig -> Ref LightButton -> impl Source #

impl ~ IO () => Op (Destroy ()) Button orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Button

Methods

runOp :: Destroy () -> orig -> Ref Button -> impl Source #

impl ~ IO () => Op (Destroy ()) OverlayWindow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.OverlayWindow

Methods

runOp :: Destroy () -> orig -> Ref OverlayWindow -> impl Source #

impl ~ IO () => Op (Destroy ()) DoubleWindow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.DoubleWindow

Methods

runOp :: Destroy () -> orig -> Ref DoubleWindow -> impl Source #

impl ~ IO () => Op (Destroy ()) SingleWindow orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.SingleWindow

Methods

runOp :: Destroy () -> orig -> Ref SingleWindow -> impl Source #

impl ~ IO () => Op (Destroy ()) Window orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Window

Methods

runOp :: Destroy () -> orig -> Ref Window -> impl Source #

impl ~ IO () => Op (Destroy ()) Group orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Group

Methods

runOp :: Destroy () -> orig -> Ref Group -> impl Source #

impl ~ IO () => Op (Destroy ()) Widget orig impl Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Widget

Methods

runOp :: Destroy () -> orig -> Ref Widget -> impl Source #

type Functions Base Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Base = ()
type Functions MultiLabel Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions SimpleTerminal Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions SVGImage Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions SystemDriver Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions ScreenDriver Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions FileInput Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions PNMImage Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions PNGImage Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions XPMImage Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions XBMImage Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions GIFImage Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions BMPImage Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions JPEGImage Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions RGBImage Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions FileBrowser Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions ColorChooser Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Spinner Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Tabs Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Scrolled Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Pack Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Tile Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions NativeFileChooser Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions TextEditor Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions TextDisplay Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions TextBuffer Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions TextSelection Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Tree Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions TreeItem Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions TreePrefs Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Clock Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions IntInput Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions SelectBrowser Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Browser Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Box Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Box = ()
type Functions GlWindow Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions TableRow Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Table Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Wizard Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Positioner Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Progress Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions ValueOutput Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions ValueInput Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Output Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Input Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions HorValueSlider Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions ValueSlider Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Scrollbar Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Counter Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Roller Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions LineDial Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions FillDial Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Dial Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Adjuster Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions ImageSurface Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions CopySurface Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Pixmap Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Bitmap Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Image Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions MenuButton Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Choice Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions SysMenuBar Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions MenuBar Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions MenuPrim Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions MenuItem Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions HorNiceSlider Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions NiceSlider Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions HorFillSlider Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions HorSlider Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions FillSlider Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Slider Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Valuator Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions ToggleButton Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions RepeatButton Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions RoundButton Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions ReturnButton Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions CheckButton Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions RadioLightButton Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions LightButton Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Button Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions OverlayWindow Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions DoubleWindow Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions SingleWindow Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Window Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Group Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Functions Widget Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Hierarchy

type Base = CBase () Source #

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

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

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

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

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

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

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

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

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

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

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

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

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

type GetIntPrim = Ptr () -> IO CInt Source #

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

newtype Width Source #

Constructors

Width Int 
Instances
Eq Width Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Methods

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

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

Ord Width Source # 
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 Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Methods

showsPrec :: Int -> Width -> ShowS #

show :: Width -> String #

showList :: [Width] -> ShowS #

newtype Height Source #

Constructors

Height Int 
Instances
Eq Height Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Methods

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

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

Ord Height Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Show Height Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

newtype Depth Source #

Constructors

Depth Int 
Instances
Eq Depth Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Methods

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

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

Ord Depth Source # 
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 Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Methods

showsPrec :: Int -> Depth -> ShowS #

show :: Depth -> String #

showList :: [Depth] -> ShowS #

newtype X Source #

Constructors

X Int 
Instances
Eq X Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Methods

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

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

Ord X Source # 
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 Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Methods

showsPrec :: Int -> X -> ShowS #

show :: X -> String #

showList :: [X] -> ShowS #

newtype Y Source #

Constructors

Y Int 
Instances
Eq Y Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Methods

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

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

Ord Y Source # 
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 Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Methods

showsPrec :: Int -> Y -> ShowS #

show :: Y -> String #

showList :: [Y] -> ShowS #

newtype ByX Source #

Constructors

ByX Double 
Instances
Eq ByX Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Methods

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

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

Ord ByX Source # 
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 Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Methods

showsPrec :: Int -> ByX -> ShowS #

show :: ByX -> String #

showList :: [ByX] -> ShowS #

newtype ByY Source #

Constructors

ByY Double 
Instances
Eq ByY Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Methods

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

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

Ord ByY Source # 
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 Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Methods

showsPrec :: Int -> ByY -> ShowS #

show :: ByY -> String #

showList :: [ByY] -> ShowS #

newtype Angle Source #

Constructors

Angle CShort 
Instances
Eq Angle Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Methods

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

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

Ord Angle Source # 
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 Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Methods

showsPrec :: Int -> Angle -> ShowS #

show :: Angle -> String #

showList :: [Angle] -> ShowS #

data DPI Source #

Constructors

DPI Float Float 
Instances
Eq DPI Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Methods

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

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

Ord DPI Source # 
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 Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Methods

showsPrec :: Int -> DPI -> ShowS #

show :: DPI -> String #

showList :: [DPI] -> ShowS #

data ByXY Source #

Constructors

ByXY ByX ByY 
Instances
Eq ByXY Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Methods

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

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

Ord ByXY Source # 
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 Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Methods

showsPrec :: Int -> ByXY -> ShowS #

show :: ByXY -> String #

showList :: [ByXY] -> ShowS #

data Size Source #

Constructors

Size Width Height 
Instances
Eq Size Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Methods

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

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

Ord Size Source # 
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 Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Methods

showsPrec :: Int -> Size -> ShowS #

show :: Size -> String #

showList :: [Size] -> ShowS #

newtype Lines Source #

Constructors

Lines Int 
Instances
Eq Lines Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Methods

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

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

Ord Lines Source # 
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 Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Methods

showsPrec :: Int -> Lines -> ShowS #

show :: Lines -> String #

showList :: [Lines] -> ShowS #

newtype AtIndex Source #

Constructors

AtIndex Int 

newtype Rows Source #

Constructors

Rows Int 
Instances
Eq Rows Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Methods

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

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

Ord Rows Source # 
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 Source # 
Instance details

Defined in Graphics.UI.FLTK.LowLevel.Fl_Types

Methods

showsPrec :: Int -> Rows -> ShowS #

show :: Rows -> String #

showList :: [Rows] -> ShowS #

newtype Columns Source #

Constructors

Columns Int 

newtype FlOffscreen Source #

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 Source #

Constructors

FlBitmask Fl_Bitmask 

newtype FlRegion Source #

Constructors

FlRegion Fl_Region 

newtype FlSocket Source #

Constructors

FlSocket Fl_Socket 

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

newtype GapSize Source #

Constructors

GapSize Int 

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

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

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

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

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