fltkhs-0.4.0.2: FLTK bindings

Safe HaskellNone
LanguageHaskell2010

Graphics.UI.FLTK.LowLevel.Dispatch

Contents

Synopsis

FindOp

type family FindOp orig hierarchy needle :: * Source

Equations

FindOp orig () n = NoFunction n orig 
FindOp orig hierarchy needle = FindOpHelper orig hierarchy needle (Contains (Functions hierarchy) needle) 

Functions

type family Functions x :: * Source

Associate a "class" with it's member functions

Instances

type Functions Base = () 
type Functions PNMImage = () 
type Functions PNGImage = () 
type Functions XPMImage = () 
type Functions XBMImage = () 
type Functions GIFImage = () 
type Functions BMPImage = () 
type Functions JPEGImage = () 
type Functions RGBImage 
type Functions FileBrowser 
type Functions ColorChooser 
type Functions Spinner 
type Functions Tabs 
type Functions Scrolled 
type Functions Pack 
type Functions Tile 
type Functions NativeFileChooser 
type Functions TextEditor 
type Functions TextDisplay 
type Functions TextBuffer 
type Functions TextSelection 
type Functions Tree 
type Functions TreeItem 
type Functions TreePrefs 
type Functions Clock 
type Functions IntInput = () 
type Functions SelectBrowser = () 
type Functions Browser 
type Functions Box = () 
type Functions GlWindow 
type Functions TableRow 
type Functions Table 
type Functions Wizard 
type Functions Positioner 
type Functions Progress 
type Functions ValueTimer = () 
type Functions HiddenTimer = () 
type Functions Timer 
type Functions ValueOutput 
type Functions ValueInput 
type Functions Output 
type Functions Input 
type Functions HorValueSlider = () 
type Functions ValueSlider 
type Functions Scrollbar 
type Functions SimpleCounter = () 
type Functions Counter 
type Functions Roller 
type Functions LineDial = () 
type Functions FillDial = () 
type Functions Dial 
type Functions Adjuster 
type Functions ImageSurface 
type Functions CopySurface 
type Functions Pixmap 
type Functions Bitmap 
type Functions Image 
type Functions MenuButton 
type Functions Choice 
type Functions SysMenuBar 
type Functions MenuPrim 
type Functions MenuItem 
type Functions HorNiceSlider = () 
type Functions NiceSlider = () 
type Functions HorFillSlider = () 
type Functions HorSlider = () 
type Functions FillSlider = () 
type Functions Slider 
type Functions Valuator 
type Functions ToggleButton 
type Functions RepeatButton 
type Functions RoundButton 
type Functions ReturnButton 
type Functions CheckButton 
type Functions RadioLightButton = () 
type Functions LightButton 
type Functions Button 
type Functions OverlayWindow 
type Functions DoubleWindow 
type Functions SingleWindow 
type Functions Window 
type Functions Group 
type Functions Widget = WidgetFuncs 
type Functions GlContext = () 
type Functions Region = () 

Match

data Match a Source

See FindOp for more details.

NoFunction

data NoFunction a b Source

See FindOp for more details.

Op

class Op op obj origObj impl where Source

Implementations of methods on various types of objects.

  • op - name of the function
  • obj - the class that implements op
  • origObj - the class in the hierarchy where the search for op started. Kept around in case the type in needed. The best example is setCallback whose implementation is usually found much lower in the hierarchy but where we also want to enforce that the implementation take the type of the widget calling it.
  • impl - a function that takes the a Ref origobj, casted down to Ref obj and whatever other parameters the instance specifies.

Methods

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

Instances

(~) * impl (IO FileBrowserType) => Op (GetFiletype ()) FileBrowser orig impl 
(~) * impl (FileBrowserType -> IO ()) => Op (SetFiletype ()) FileBrowser orig impl 
(~) * impl (IO CUChar) => Op (GetIconsize ()) FileBrowser orig impl 
(~) * impl (CUChar -> IO ()) => Op (SetIconsize ()) FileBrowser orig impl 
(~) * impl ((Between0And1, Between0And1, Between0And1) -> IO (Either NoChange ())) => Op (SetRgb ()) ColorChooser orig impl 
(~) * impl ((Between0And6, Between0And1, Between0And1) -> IO (Either NoChange ())) => Op (SetHsv ()) ColorChooser orig impl 
(~) * impl (IO (Either OutOfRange Between0And1)) => Op (GetB ()) ColorChooser orig impl 
(~) * impl (IO (Either OutOfRange Between0And1)) => Op (GetG ()) ColorChooser orig impl 
(~) * impl (IO (Either OutOfRange Between0And1)) => Op (GetR ()) ColorChooser orig impl 
(~) * impl (IO (Either OutOfRange Between0And1)) => Op (GetSaturation ()) ColorChooser orig impl 
(~) * impl (IO (Either OutOfRange Between0And6)) => Op (GetHue ()) ColorChooser orig impl 
(~) * impl (IO (Maybe String)) => Op (GetFormat ()) Spinner orig impl 
(~) * impl (TabsHeightOffset -> IO Rectangle) => Op (ClientArea ()) Tabs orig impl 
(~) * impl (Position -> IO (Maybe (Ref Widget))) => Op (Which ()) Tabs orig impl 
(Parent a Widget, (~) * impl (Maybe (Ref a) -> IO (Either NoChange ()))) => Op (SetPush ()) Tabs orig impl 
(~) * impl (IO (Maybe (Ref Widget))) => Op (GetPush ()) Tabs orig impl 
(~) * impl (IO Int) => Op (Yposition ()) Scrolled orig impl 
(~) * impl (IO Int) => Op (Xposition ()) Scrolled orig impl 
(~) * impl (Position -> IO ()) => Op (ScrollTo ()) Scrolled orig impl 
(~) * impl (IO Bool) => Op (IsHorizontal ()) Pack orig impl 
(~) * impl (IO Int) => Op (GetSpacing ()) Pack orig impl 
(~) * impl (Int -> IO ()) => Op (SetSpacing ()) Pack orig impl 
(~) * impl (IO (Maybe String)) => Op (GetErrmsg ()) NativeFileChooser orig impl 
(~) * impl (IO (Maybe String)) => Op (GetPresetFile ()) NativeFileChooser orig impl 
(~) * impl (String -> IO ()) => Op (SetPresetFile ()) NativeFileChooser orig impl 
(~) * impl (IO Int) => Op (GetFilterValue ()) NativeFileChooser orig impl 
(~) * impl (Int -> IO ()) => Op (SetFilterValue ()) NativeFileChooser orig impl 
(~) * impl (IO Int) => Op (Filters ()) NativeFileChooser orig impl 
(~) * impl (String -> IO ()) => Op (SetFilter ()) FileBrowser orig impl 
(~) * impl (String -> IO ()) => Op (SetFilter ()) NativeFileChooser orig impl 
(~) * impl (IO String) => Op (GetFilter ()) FileBrowser orig impl 
(~) * impl (IO (Maybe String)) => Op (GetFilter ()) NativeFileChooser orig impl 
(~) * impl (IO (Maybe String)) => Op (GetTitle ()) NativeFileChooser orig impl 
(~) * impl (String -> IO ()) => Op (SetTitle ()) NativeFileChooser orig impl 
(~) * impl (IO (Maybe String)) => Op (GetDirectory ()) NativeFileChooser orig impl 
(~) * impl (String -> IO ()) => Op (SetDirectory ()) NativeFileChooser orig impl 
(~) * impl (Int -> IO (Maybe String)) => Op (GetFilenameAt ()) NativeFileChooser orig impl 
(~) * impl (IO (Maybe String)) => Op (GetFilename ()) NativeFileChooser orig impl 
(~) * impl (IO [NativeFileChooserOption]) => Op (GetOptions ()) NativeFileChooser orig impl 
(~) * impl ([NativeFileChooserOption] -> IO ()) => Op (SetOptions ()) NativeFileChooser orig impl 
(~) * impl ([KeyBinding] -> IO ()) => Op (ReplaceKeyBindings ()) TextEditor orig impl 
(~) * impl (IO [KeyBinding]) => Op (GetDefaultKeyBindings ()) TextEditor orig impl 
(~) * impl (IO Bool) => Op (GetInsertMode ()) TextEditor orig impl 
(~) * impl (Bool -> IO ()) => Op (SetInsertMode ()) TextEditor orig impl 
(~) * impl (IO String) => Op (GetLinenumberFormat ()) TextDisplay orig impl 
(~) * impl (String -> IO ()) => Op (SetLinenumberFormat ()) TextDisplay orig impl 
(~) * impl (IO AlignType) => Op (GetLinenumberAlign ()) TextDisplay orig impl 
(~) * impl (AlignType -> IO ()) => Op (SetLinenumberAlign ()) TextDisplay orig impl 
(~) * impl (IO Color) => Op (GetLinenumberBgcolor ()) TextDisplay orig impl 
(~) * impl (Color -> IO ()) => Op (SetLinenumberBgcolor ()) TextDisplay orig impl 
(~) * impl (IO Color) => Op (GetLinenumberFgcolor ()) TextDisplay orig impl 
(~) * impl (Color -> IO ()) => Op (SetLinenumberFgcolor ()) TextDisplay orig impl 
(~) * impl (IO FontSize) => Op (GetLinenumberSize ()) TextDisplay orig impl 
(~) * impl (FontSize -> IO ()) => Op (SetLinenumberSize ()) TextDisplay orig impl 
(~) * impl (IO Font) => Op (GetLinenumberFont ()) TextDisplay orig impl 
(~) * impl (Font -> IO ()) => Op (SetLinenumberFont ()) TextDisplay orig impl 
(~) * impl (IO Width) => Op (GetLinenumberWidth ()) TextDisplay orig impl 
(~) * impl (Width -> IO ()) => Op (SetLinenumberWidth ()) TextDisplay orig impl 
(~) * impl (Double -> IO Double) => Op (ColToX ()) TextDisplay orig impl 
(~) * impl (Double -> IO Double) => Op (XToCol ()) TextDisplay orig impl 
(~) * impl (BufferOffset -> Int -> Int -> IO TextDisplayStyle) => Op (PositionStyle ()) TextDisplay orig impl 
(Parent a TextBuffer, (~) * impl (Ref a -> [(Char, StyleTableEntry)] -> Maybe (Char, UnfinishedStyleCb) -> IO ())) => Op (HighlightData ()) TextDisplay orig impl 
(~) * impl (AlignType -> IO ()) => Op (SetScrollbarAlign ()) TextDisplay orig impl 
(~) * impl (IO AlignType) => Op (GetScrollbarAlign ()) TextDisplay orig impl 
(~) * impl (CursorType -> IO ()) => Op (SetCursorStyle ()) TextDisplay orig impl 
(~) * impl (Bool -> IO ()) => Op (ShowCursor ()) TextDisplay orig impl 
(~) * impl (IO ()) => Op (PreviousWord ()) TextDisplay orig impl 
(~) * impl (IO ()) => Op (NextWord ()) TextDisplay orig impl 
(~) * impl (IO (Either OutOfRange ())) => Op (MoveDown ()) TextDisplay orig impl 
(~) * impl (IO (Either OutOfRange ())) => Op (MoveUp ()) TextDisplay orig impl 
(~) * impl (IO (Either OutOfRange ())) => Op (MoveLeft ()) TextDisplay orig impl 
(~) * impl (IO (Either OutOfRange ())) => Op (MoveRight ()) TextDisplay orig impl 
(~) * impl (IO ()) => Op (ShowInsertPosition ()) TextDisplay orig impl 
(~) * impl (Position -> IO Bool) => Op (InSelection ()) TextDisplay orig impl 
(~) * impl (BufferOffset -> IO (Either OutOfRange Position)) => Op (PositionToXy ()) TextDisplay orig impl 
(~) * impl (IO BufferOffset) => Op (GetInsertPosition ()) TextDisplay orig impl 
(~) * impl (BufferOffset -> IO ()) => Op (SetInsertPosition ()) TextDisplay orig impl 
(~) * impl (String -> IO ()) => Op (Overstrike ()) TextDisplay orig impl 
(~) * impl (Int -> BufferOffset -> IO ()) => Op (Scroll ()) TextDisplay orig impl 
(~) * impl (BufferRange -> IO ()) => Op (RedisplayRange ()) TextDisplay orig impl 
(~) * impl (IO (Maybe (Ref TextBuffer))) => Op (GetBuffer ()) TextDisplay orig impl 
(Parent a TextBuffer, (~) * impl (Maybe (Ref a) -> IO ())) => Op (SetBuffer ()) TextDisplay orig impl 
(~) * impl (BufferOffset -> IO (Either OutOfRange BufferOffset)) => Op (Utf8Align ()) TextBuffer orig impl 
(~) * impl (BufferOffset -> IO BufferOffset) => Op (NextCharClipped ()) TextBuffer orig impl 
(~) * impl (BufferOffset -> IO BufferOffset) => Op (NextChar ()) TextBuffer orig impl 
(~) * impl (BufferOffset -> IO (Either OutOfRange BufferOffset)) => Op (PrevCharClipped ()) TextBuffer orig impl 
(~) * impl (BufferOffset -> IO (Either OutOfRange BufferOffset)) => Op (PrevChar ()) TextBuffer orig impl 
(~) * impl (IO (Maybe (Ref TextSelection))) => Op (HighlightSelection ()) TextBuffer orig impl 
(~) * impl (IO (Maybe (Ref TextSelection))) => Op (SecondarySelection ()) TextBuffer orig impl 
(~) * impl (IO (Maybe (Ref TextSelection))) => Op (PrimarySelection ()) TextBuffer orig impl 
(~) * impl (BufferOffset -> String -> Bool -> IO (Either NotFound BufferOffset)) => Op (SearchBackwardWithMatchcase ()) TextBuffer orig impl 
(~) * impl (BufferOffset -> String -> Bool -> IO (Either NotFound BufferOffset)) => Op (SearchForwardWithMatchcase ()) TextBuffer orig impl 
(~) * impl (BufferOffset -> Char -> IO (Either NotFound BufferOffset)) => Op (FindcharBackward ()) TextBuffer orig impl 
(~) * impl (BufferOffset -> Char -> IO (Either NotFound BufferOffset)) => Op (FindcharForward ()) TextBuffer orig impl 
(~) * impl (BufferOffset -> Int -> IO BufferOffset) => Op (RewindLines ()) TextDisplay orig impl 
(~) * impl (BufferOffset -> Int -> IO Int) => Op (RewindLines ()) TextBuffer orig impl 
(~) * impl (BufferOffset -> Int -> Bool -> IO BufferOffset) => Op (SkipLines ()) TextDisplay orig impl 
(~) * impl (BufferOffset -> Int -> IO BufferOffset) => Op (SkipLines ()) TextBuffer orig impl 
(~) * impl (BufferRange -> Bool -> IO Int) => Op (CountLines ()) TextDisplay orig impl 
(~) * impl (BufferRange -> IO Int) => Op (CountLines ()) TextBuffer orig impl 
(~) * impl (BufferOffset -> Int -> IO BufferOffset) => Op (SkipDisplayedCharacters ()) TextBuffer orig impl 
(~) * impl (BufferRange -> IO Int) => Op (CountDisplayedCharacters ()) TextBuffer orig impl 
(~) * impl (BufferOffset -> IO BufferOffset) => Op (WordEnd ()) TextDisplay orig impl 
(~) * impl (BufferOffset -> IO (Either OutOfRange BufferOffset)) => Op (WordEnd ()) TextBuffer orig impl 
(~) * impl (BufferOffset -> IO BufferOffset) => Op (WordStart ()) TextDisplay orig impl 
(~) * impl (BufferOffset -> IO (Either OutOfRange BufferOffset)) => Op (WordStart ()) TextBuffer orig impl 
(~) * impl (BufferOffset -> Bool -> IO BufferOffset) => Op (LineEnd ()) TextDisplay orig impl 
(~) * impl (Int -> IO (Either OutOfRange BufferOffset)) => Op (LineEnd ()) TextBuffer orig impl 
(~) * impl (BufferOffset -> IO BufferOffset) => Op (LineStart ()) TextDisplay orig impl 
(~) * impl (Int -> IO (Either OutOfRange BufferOffset)) => Op (LineStart ()) TextBuffer orig impl 
(~) * impl (Int -> IO (Either OutOfRange String)) => Op (LineText ()) TextBuffer orig impl 
(~) * impl (IO ()) => Op (CallPredeleteCallbacks ()) TextBuffer orig impl 
(~) * impl (FunPtr () -> IO ()) => Op (RemovePredeleteCallback ()) TextBuffer orig impl 
(~) * impl (TextPredeleteCb -> IO (FunPtr ())) => Op (AddPredeleteCallback ()) TextBuffer orig impl 
(~) * impl (IO ()) => Op (CallModifyCallbacks ()) TextBuffer orig impl 
(~) * impl (FunPtr () -> IO ()) => Op (RemoveModifyCallback ()) TextBuffer orig impl 
(~) * impl (TextModifyCb -> IO (FunPtr ())) => Op (AddModifyCallback ()) TextBuffer orig impl 
(~) * impl (IO String) => Op (HighlightText ()) TextBuffer orig impl 
(~) * impl (IO (Maybe BufferRange)) => Op (HighlightPosition ()) TextBuffer orig impl 
(~) * impl (IO ()) => Op (Unhighlight ()) TextBuffer orig impl 
(~) * impl (BufferRange -> IO ()) => Op (SetHighlight ()) TextBuffer orig impl 
(~) * impl (IO Bool) => Op (GetHighlight ()) TextBuffer orig impl 
(~) * impl (String -> IO ()) => Op (ReplaceSecondarySelection ()) TextBuffer orig impl 
(~) * impl (IO ()) => Op (RemoveSecondarySelection ()) TextBuffer orig impl 
(~) * impl (IO String) => Op (SecondarySelectionText ()) TextBuffer orig impl 
(~) * impl (IO BufferRange) => Op (SecondarySelectionPosition ()) TextBuffer orig impl 
(~) * impl (IO ()) => Op (SecondaryUnselect ()) TextBuffer orig impl 
(~) * impl (IO Bool) => Op (SecondarySelected ()) TextBuffer orig impl 
(~) * impl (BufferRange -> IO ()) => Op (SecondarySelect ()) TextBuffer orig impl 
(~) * impl (String -> IO ()) => Op (ReplaceSelection ()) TextBuffer orig impl 
(~) * impl (IO ()) => Op (RemoveSelection ()) TextBuffer orig impl 
(~) * impl (IO String) => Op (SelectionText ()) TextBuffer orig impl 
(~) * impl (IO BufferRange) => Op (SelectionPosition ()) TextBuffer orig impl 
(~) * impl (IO ()) => Op (Unselect ()) TextBuffer orig impl 
(~) * impl (Int -> IO ()) => Op (SetTabDistance ()) TextBuffer orig impl 
(~) * impl (IO Int) => Op (GetTabDistance ()) TextBuffer orig impl 
(~) * impl (String -> Int -> IO (Either DataProcessingError ())) => Op (SavefileWithBuflen ()) TextBuffer orig impl 
(~) * impl (String -> IO (Either DataProcessingError ())) => Op (Savefile ()) TextBuffer orig impl 
(~) * impl (String -> BufferRange -> Int -> IO (Either DataProcessingError ())) => Op (OutputfileWithBuflen ()) TextBuffer orig impl 
(~) * impl (String -> BufferRange -> IO (Either DataProcessingError ())) => Op (Outputfile ()) TextBuffer orig impl 
(~) * impl (String -> Int -> IO (Either DataProcessingError ())) => Op (LoadfileWithBuflen ()) TextBuffer orig impl 
(~) * impl (String -> IO (Either DataProcessingError ())) => Op (Loadfile ()) TextBuffer orig impl 
(~) * impl (String -> Int -> IO (Either DataProcessingError ())) => Op (AppendfileWithBuflen ()) TextBuffer orig impl 
(~) * impl (String -> IO (Either DataProcessingError ())) => Op (Appendfile ()) TextBuffer orig impl 
(~) * impl (String -> BufferOffset -> Int -> IO (Either DataProcessingError ())) => Op (InsertfileWithBuflen ()) TextBuffer orig impl 
(~) * impl (String -> BufferOffset -> IO (Either DataProcessingError ())) => Op (Insertfile ()) TextBuffer orig impl 
(~) * impl (Bool -> IO ()) => Op (CanUndo ()) TextBuffer orig impl 
(~) * impl (String -> IO ()) => Op (AppendToBuffer ()) TextBuffer orig impl 
(~) * impl (BufferOffset -> IO Char) => Op (ByteAt ()) TextBuffer orig impl 
(~) * impl (BufferOffset -> IO Char) => Op (CharAt ()) TextBuffer orig impl 
(~) * impl (BufferRange -> IO String) => Op (TextRange ()) TextBuffer orig impl 
(~) * impl (IO Int) => Op (GetLength ()) TextBuffer orig impl 
(~) * impl (IO String) => Op (FileEncodingWarningMessage ()) TextBuffer orig impl 
(~) * impl (IO Bool) => Op (InputFileWasTranscoded ()) TextBuffer orig impl 
(~) * impl (BufferOffset -> IO Bool) => Op (Includes ()) TextSelection orig impl 
(~) * impl (Bool -> IO ()) => Op (SetSelected ()) TextSelection orig impl 
(~) * impl (IO BufferOffset) => Op (Start ()) TextSelection orig impl 
(~) * impl (BufferOffset -> Int -> Int -> IO ()) => Op (Update ()) TextSelection orig impl 
(~) * impl (IO TreeReasonType) => Op (GetCallbackReason ()) Tree orig impl 
(~) * impl (TreeReasonType -> IO ()) => Op (SetCallbackReason ()) Tree orig impl 
(~) * impl (IO (Maybe (Ref TreeItem))) => Op (GetCallbackItem ()) Tree orig impl 
(Parent a TreeItem, (~) * impl (Ref a -> IO ())) => Op (SetCallbackItem ()) Tree orig impl 
(~) * impl (IO Bool) => Op (IsVscrollVisible ()) Tree orig impl 
(Parent a Widget, (~) * impl (Ref a -> IO Bool)) => Op (IsScrollbar ()) Tree orig impl 
(~) * impl (Int -> IO ()) => Op (SetVposition ()) Tree orig impl 
(~) * impl (IO Int) => Op (GetVposition ()) Tree orig impl 
(~) * impl (Ref TreeItem -> IO ()) => Op (Display ()) Tree orig impl 
(~) * impl (Ref TreeItem -> IO ()) => Op (ShowItemBottom ()) Tree orig impl 
(~) * impl (Ref TreeItem -> IO ()) => Op (ShowItemMiddle ()) Tree orig impl 
(~) * impl (Ref TreeItem -> IO ()) => Op (ShowItemTop ()) Tree orig impl 
(~) * impl (Ref TreeItem -> Maybe Int -> IO ()) => Op (ShowItemWithYoff ()) Tree orig impl 
(~) * impl (IO TreeSelect) => Op (Selectmode ()) Tree orig impl 
(~) * impl (IO Color) => Op (GetItemLabelfgcolor ()) Tree orig impl 
(~) * impl (Font -> IO ()) => Op (SetItemLabelfont ()) Tree orig impl 
(~) * impl (IO (Maybe (Ref TreeItem))) => Op (GetItemFocus ()) Tree orig impl 
(~) * impl (Ref TreeItem -> IO ()) => Op (SetItemFocus ()) Tree orig impl 
(~) * impl (Maybe (Ref TreeItem) -> Bool -> IO ()) => Op (DeselectAllAndCallback ()) Tree orig impl 
(~) * impl (Maybe (Ref TreeItem) -> Bool -> IO ()) => Op (SelectAllAndCallback ()) Tree orig impl 
(~) * impl (Ref TreeItem -> Bool -> IO ()) => Op (SelectToggleAndCallback ()) Tree orig impl 
(~) * impl (TreeItemLocator -> Bool -> IO ()) => Op (SelectAndCallback ()) Tree orig impl 
(~) * impl (TreeItemLocator -> Bool -> IO ()) => Op (CloseAndCallback ()) Tree orig impl 
(~) * impl (Ref TreeItem -> Bool -> IO ()) => Op (OpenToggleAndCallback ()) Tree orig impl 
(~) * impl (TreeItemLocator -> Bool -> IO ()) => Op (OpenAndCallback ()) Tree orig impl 
(~) * impl (Ref TreeItem -> Maybe SearchDirection -> IO (Maybe (Ref TreeItem))) => Op (NextSelectedItemAfterItem ()) Tree orig impl 
(~) * impl (IO (Maybe (Ref TreeItem))) => Op (NextSelectedItem ()) Tree orig impl 
(~) * impl (IO (Maybe (Ref TreeItem))) => Op (LastSelectedItem ()) Tree orig impl 
(~) * impl (IO (Maybe (Ref TreeItem))) => Op (FirstSelectedItem ()) Tree orig impl 
(~) * impl (IO (Maybe (Ref TreeItem))) => Op (LastVisible ()) Tree orig impl 
(~) * impl (IO (Maybe (Ref TreeItem))) => Op (GetLast ()) Tree orig impl 
(~) * impl (Ref TreeItem -> IO (Maybe (Ref TreeItem))) => Op (PrevBeforeItem ()) Tree orig impl 
(~) * impl (Ref TreeItem -> Maybe SearchDirection -> Bool -> IO (Maybe (Ref TreeItem))) => Op (NextItem ()) Tree orig impl 
(~) * impl (Ref TreeItem -> IO (Maybe (Ref TreeItem))) => Op (NextAfterItem ()) Tree orig impl 
(~) * impl (IO (Maybe (Ref TreeItem))) => Op (FirstVisible ()) Tree orig impl 
(~) * impl (IO (Maybe (Ref TreeItem))) => Op (ItemClicked ()) Tree orig impl 
(~) * impl (IO (Maybe (Ref TreeItem))) => Op (Root ()) Tree orig impl 
(~) * impl (String -> IO ()) => Op (RootLabel ()) Tree orig impl 
(~) * impl (IO Int) => Op (LabelH ()) TreeItem orig impl 
(~) * impl (IO Int) => Op (LabelW ()) TreeItem orig impl 
(~) * impl (IO Int) => Op (LabelY ()) TreeItem orig impl 
(~) * impl (IO Int) => Op (LabelX ()) TreeItem orig impl 
(~) * impl (IO Bool) => Op (IsRoot ()) TreeItem orig impl 
(Parent a TreePrefs, (~) * impl (Ref a -> IO Int)) => Op (EventOnLabel ()) TreeItem orig impl 
(Parent a TreePrefs, (~) * impl (Ref a -> IO Int)) => Op (EventOnCollapseIcon ()) TreeItem orig impl 
(Parent a TreePrefs, (~) * impl (Ref a -> IO (Maybe (Ref TreeItem)))) => Op (FindClicked ()) TreeItem orig impl 
(~) * impl (IO Bool) => Op (VisibleR ()) TreeItem orig impl 
(~) * impl (IO Bool) => Op (IsVisible ()) TreeItem orig impl 
(~) * impl (IO Bool) => Op (IsActive ()) TreeItem orig impl 
(~) * impl (Bool -> IO ()) => Op (ActivateWith ()) TreeItem orig impl 
(~) * impl (IO ()) => Op (DeselectAll ()) Tree orig impl 
(~) * impl (IO Int) => Op (DeselectAll ()) TreeItem orig impl 
(~) * impl (IO ()) => Op (SelectAll ()) Tree orig impl 
(~) * impl (IO Int) => Op (SelectAll ()) TreeItem orig impl 
(~) * impl (Ref TreeItem -> IO ()) => Op (SelectToggle ()) Tree orig impl 
(~) * impl (IO ()) => Op (SelectToggle ()) TreeItem orig impl 
(~) * impl (Int -> IO ()) => Op (SelectWithVal ()) TreeItem orig impl 
(~) * impl (Ref TreeItem -> IO ()) => Op (OpenToggle ()) Tree orig impl 
(~) * impl (IO ()) => Op (OpenToggle ()) TreeItem orig impl 
(~) * impl (TreeItemLocator -> IO Bool) => Op (IsClose ()) Tree orig impl 
(~) * impl (IO Bool) => Op (IsClose ()) TreeItem orig impl 
(~) * impl (TreeItemLocator -> IO Bool) => Op (IsOpen ()) Tree orig impl 
(~) * impl (IO Bool) => Op (IsOpen ()) TreeItem orig impl 
(~) * impl (TreeItemLocator -> IO ()) => Op (Close ()) Tree orig impl 
(~) * impl (IO ()) => Op (Close ()) TreeItem orig impl 
(~) * impl (TreeItemLocator -> IO ()) => Op (Open ()) Tree orig impl 
(~) * impl (IO ()) => Op (Open ()) TreeItem orig impl 
(Parent a TreePrefs, (~) * impl (Ref a -> IO (Maybe (Ref TreeItem)))) => Op (PrevDisplayed ()) TreeItem orig impl 
(Parent a TreePrefs, (~) * impl (Ref a -> IO (Maybe (Ref TreeItem)))) => Op (NextDisplayed ()) TreeItem orig impl 
(~) * impl (Int -> IO ()) => Op (UpdatePrevNext ()) TreeItem orig impl 
(~) * impl (IO (Maybe (Ref TreeItem))) => Op (PrevSibling ()) TreeItem orig impl 
(~) * impl (IO (Maybe (Ref TreeItem))) => Op (NextSibling ()) TreeItem orig impl 
(~) * impl (IO Int) => Op (GetDepth ()) TreeItem orig impl 
(Parent a TreeItem, (~) * impl (Ref a -> MoveType -> IO (Either MoveError ()))) => Op (MoveTo ()) TreeItem orig impl 
(Parent a TreeItem, (~) * impl (Ref a -> Int -> IO (Either UnknownError ()))) => Op (Reparent ()) TreeItem orig impl 
(~) * impl (Int -> IO (Either UnknownError (Ref orig))) => Op (Deparent ()) TreeItem orig impl 
(Parent a TreeItem, (~) * impl (Ref a -> String -> IO (Maybe (Ref a)))) => Op (InsertAbove ()) Tree orig impl 
(Parent a TreePrefs, (~) * impl (Ref a -> String -> IO (Maybe (Ref TreeItem)))) => Op (InsertAbove ()) TreeItem orig impl 
(Parent a TreeItem, (~) * impl (String -> Ref a -> IO (Maybe (Ref TreeItem)))) => Op (AddAt ()) Tree orig impl 
(Parent a TreeItem, Parent b TreePrefs, (~) * impl (Ref b -> [String] -> Maybe (Ref a) -> IO (Maybe (Ref a)))) => Op (AddAt ()) TreeItem orig impl 
(~) * impl (String -> IO (Maybe (Ref TreeItem))) => Op (FindItem ()) Tree orig impl 
(~) * impl ([String] -> IO (Maybe (Ref TreeItem))) => Op (FindItem ()) TreeItem orig impl 
(~) * impl ([String] -> IO (Maybe (Ref TreeItem))) => Op (FindInChildren ()) TreeItem orig impl 
(Parent a TreeItem, (~) * impl (Ref a -> Ref a -> IO (Either TreeItemNotFound ()))) => Op (SwapChildrenByTreeItem ()) TreeItem orig impl 
(~) * impl (Int -> Int -> IO ()) => Op (SwapChildren ()) TreeItem orig impl 
(Parent a TreeItem, (~) * impl (Ref a -> IO ())) => Op (ClearChildren ()) Tree orig impl 
(~) * impl (IO ()) => Op (ClearChildren ()) TreeItem orig impl 
(~) * impl (TreeItemLocator -> IO (Either UnknownError ())) => Op (RemoveChild ()) TreeItem orig impl 
(~) * impl (TreeItemLocator -> IO (Maybe TreeItemIndex)) => Op (FindChild ()) TreeItem orig impl 
(~) * impl (IO Bool) => Op (HasChildren ()) TreeItem orig impl 
(~) * impl (Int -> IO (Maybe (Ref Widget))) => Op (Child ()) TreeItem orig impl 
(~) * impl (IO (Maybe (Ref Widget))) => Op (GetWidget ()) TreeItem orig impl 
(Parent a Widget, (~) * impl (Maybe (Ref a) -> IO ())) => Op (SetWidget ()) TreeItem orig impl 
(~) * impl (IO ()) => Op (ShowSelf ()) Tree orig impl 
(~) * impl (Maybe String -> IO ()) => Op (ShowSelf ()) TreeItem orig impl 
(~) * impl (TreeSelect -> IO ()) => Op (SetSelectmode ()) Tree orig impl 
(~) * impl (TreeSelect -> IO ()) => Op (SetSelectmode ()) TreePrefs orig impl 
(~) * impl (IO TreeSelect) => Op (GetSelectmode ()) TreePrefs orig impl 
(~) * impl (Bool -> IO ()) => Op (SetShowroot ()) Tree orig impl 
(~) * impl (Bool -> IO ()) => Op (SetShowroot ()) TreePrefs orig impl 
(~) * impl (IO Bool) => Op (GetShowroot ()) Tree orig impl 
(~) * impl (IO Bool) => Op (GetShowroot ()) TreePrefs orig impl 
(~) * impl (Boxtype -> IO ()) => Op (SetSelectbox ()) Tree orig impl 
(~) * impl (Boxtype -> IO ()) => Op (SetSelectbox ()) TreePrefs orig impl 
(~) * impl (IO Boxtype) => Op (GetSelectbox ()) Tree orig impl 
(~) * impl (IO Boxtype) => Op (GetSelectbox ()) TreePrefs orig impl 
(~) * impl (TreeSort -> IO ()) => Op (SetSortorder ()) Tree orig impl 
(~) * impl (TreeSort -> IO ()) => Op (SetSortorder ()) TreePrefs orig impl 
(~) * impl (IO TreeSort) => Op (GetSortorder ()) Tree orig impl 
(~) * impl (IO TreeSort) => Op (GetSortorder ()) TreePrefs orig impl 
(~) * impl (Bool -> IO ()) => Op (SetShowcollapse ()) Tree orig impl 
(~) * impl (Bool -> IO ()) => Op (SetShowcollapse ()) TreePrefs orig impl 
(~) * impl (IO Bool) => Op (GetShowcollapse ()) Tree orig impl 
(~) * impl (IO Bool) => Op (GetShowcollapse ()) TreePrefs orig impl 
(Parent a Image, (~) * impl (Maybe (Ref a) -> IO ())) => Op (SetUsericon ()) Tree orig impl 
(Parent a Image, (~) * impl (Maybe (Ref a) -> IO ())) => Op (SetUsericon ()) TreeItem orig impl 
(Parent a Image, (~) * impl (Maybe (Ref a) -> IO ())) => Op (SetUsericon ()) TreePrefs orig impl 
(~) * impl (IO (Maybe (Ref Image))) => Op (GetUsericon ()) Tree orig impl 
(~) * impl (IO (Maybe (Ref Image))) => Op (GetUsericon ()) TreeItem orig impl 
(~) * impl (IO (Maybe (Ref Image))) => Op (GetUsericon ()) TreePrefs orig impl 
(Parent a Image, (~) * impl (Maybe (Ref a) -> IO ())) => Op (SetCloseicon ()) Tree orig impl 
(Parent a Image, (~) * impl (Maybe (Ref a) -> IO ())) => Op (SetCloseicon ()) TreePrefs orig impl 
(~) * impl (IO (Maybe (Ref Image))) => Op (GetCloseicon ()) Tree orig impl 
(~) * impl (IO (Maybe (Ref Image))) => Op (GetCloseicon ()) TreePrefs orig impl 
(Parent a Image, (~) * impl (Maybe (Ref a) -> IO ())) => Op (SetOpenicon ()) Tree orig impl 
(Parent a Image, (~) * impl (Maybe (Ref a) -> IO ())) => Op (SetOpenicon ()) TreePrefs orig impl 
(~) * impl (IO (Maybe (Ref Image))) => Op (GetOpenicon ()) Tree orig impl 
(~) * impl (IO (Maybe (Ref Image))) => Op (GetOpenicon ()) TreePrefs orig impl 
(~) * impl (Int -> IO ()) => Op (SetConnectorwidth ()) Tree orig impl 
(~) * impl (Int -> IO ()) => Op (SetConnectorwidth ()) TreePrefs orig impl 
(~) * impl (IO Int) => Op (GetConnectorwidth ()) Tree orig impl 
(~) * impl (IO Int) => Op (GetConnectorwidth ()) TreePrefs orig impl 
(~) * impl (TreeConnector -> IO ()) => Op (SetConnectorstyle ()) Tree orig impl 
(~) * impl (TreeConnector -> IO ()) => Op (SetConnectorstyle ()) TreePrefs orig impl 
(~) * impl (IO TreeConnector) => Op (GetConnectorstyle ()) Tree orig impl 
(~) * impl (IO TreeConnector) => Op (GetConnectorstyle ()) TreePrefs orig impl 
(~) * impl (Color -> IO ()) => Op (SetConnectorcolor ()) Tree orig impl 
(~) * impl (Color -> IO ()) => Op (SetConnectorcolor ()) TreePrefs orig impl 
(~) * impl (IO Color) => Op (GetConnectorcolor ()) Tree orig impl 
(~) * impl (IO Color) => Op (GetConnectorcolor ()) TreePrefs orig impl 
(~) * impl (Int -> IO ()) => Op (SetLinespacing ()) Tree orig impl 
(~) * impl (Int -> IO ()) => Op (SetLinespacing ()) TreePrefs orig impl 
(~) * impl (IO Int) => Op (GetLinespacing ()) Tree orig impl 
(~) * impl (IO Int) => Op (GetLinespacing ()) TreePrefs orig impl 
(~) * impl (Int -> IO ()) => Op (SetLabelmarginleft ()) Tree orig impl 
(~) * impl (Int -> IO ()) => Op (SetLabelmarginleft ()) TreePrefs orig impl 
(~) * impl (IO Int) => Op (GetLabelmarginleft ()) Tree orig impl 
(~) * impl (IO Int) => Op (GetLabelmarginleft ()) TreePrefs orig impl 
(~) * impl (Int -> IO ()) => Op (SetUsericonmarginleft ()) Tree orig impl 
(~) * impl (Int -> IO ()) => Op (SetUsericonmarginleft ()) TreePrefs orig impl 
(~) * impl (IO Int) => Op (GetUsericonmarginleft ()) Tree orig impl 
(~) * impl (IO Int) => Op (GetUsericonmarginleft ()) TreePrefs orig impl 
(~) * impl (Int -> IO ()) => Op (SetOpenchildMarginbottom ()) Tree orig impl 
(~) * impl (Int -> IO ()) => Op (SetOpenchildMarginbottom ()) TreePrefs orig impl 
(~) * impl (IO Int) => Op (GetOpenchildMarginbottom ()) Tree orig impl 
(~) * impl (IO Int) => Op (GetOpenchildMarginbottom ()) TreePrefs orig impl 
(~) * impl (Int -> IO ()) => Op (SetMargintop ()) Tree orig impl 
(~) * impl (Int -> IO ()) => Op (SetMargintop ()) TreePrefs orig impl 
(~) * impl (IO Int) => Op (GetMargintop ()) Tree orig impl 
(~) * impl (IO Int) => Op (GetMargintop ()) TreePrefs orig impl 
(~) * impl (Int -> IO ()) => Op (SetMarginleft ()) Tree orig impl 
(~) * impl (Int -> IO ()) => Op (SetMarginleft ()) TreePrefs orig impl 
(~) * impl (IO Int) => Op (GetMarginleft ()) Tree orig impl 
(~) * impl (IO Int) => Op (GetMarginleft ()) TreePrefs orig impl 
(~) * impl (Color -> IO ()) => Op (SetLabelbgcolor ()) TreeItem orig impl 
(~) * impl (Color -> IO ()) => Op (SetLabelbgcolor ()) TreePrefs orig impl 
(~) * impl (IO Color) => Op (GetLabelbgcolor ()) TreeItem orig impl 
(~) * impl (IO Color) => Op (GetLabelbgcolor ()) TreePrefs orig impl 
(~) * impl (Color -> IO ()) => Op (SetLabelfgcolor ()) TreeItem orig impl 
(~) * impl (Color -> IO ()) => Op (SetLabelfgcolor ()) TreePrefs orig impl 
(~) * impl (IO Color) => Op (GetLabelfgcolor ()) TreeItem orig impl 
(~) * impl (IO Color) => Op (GetLabelfgcolor ()) TreePrefs orig impl 
(~) * impl (Color -> IO ()) => Op (SetItemLabelbgcolor ()) Tree orig impl 
(~) * impl (Color -> IO ()) => Op (SetItemLabelbgcolor ()) TreePrefs orig impl 
(~) * impl (IO Color) => Op (GetItemLabelbgcolor ()) Tree orig impl 
(~) * impl (IO Color) => Op (GetItemLabelbgcolor ()) TreePrefs orig impl 
(~) * impl (Color -> IO ()) => Op (SetItemLabelfgcolor ()) Tree orig impl 
(~) * impl (Color -> IO ()) => Op (SetItemLabelfgcolor ()) TreePrefs orig impl 
(~) * impl (FontSize -> IO ()) => Op (SetItemLabelsize ()) Tree orig impl 
(~) * impl (FontSize -> IO ()) => Op (SetItemLabelsize ()) TreePrefs orig impl 
(~) * impl (IO FontSize) => Op (GetItemLabelsize ()) Tree orig impl 
(~) * impl (IO FontSize) => Op (GetItemLabelsize ()) TreePrefs orig impl 
(~) * impl (IO Font) => Op (GetItemLabelfont ()) Tree orig impl 
(~) * impl (IO Font) => Op (GetItemLabelfont ()) TreePrefs orig impl 
(~) * impl (IO ClockSinceEpoch) => Op (GetValueSinceEpoch ()) Clock orig impl 
(~) * impl (IO ()) => Op (Sort ()) Browser orig impl 
(~) * impl (SortType -> IO ()) => Op (SortWithSortType ()) Browser orig impl 
(~) * impl (Width -> IO ()) => Op (SetScrollbarWidth ()) TextDisplay orig impl 
(~) * impl (Int -> IO ()) => Op (SetScrollbarWidth ()) Browser orig impl 
(~) * impl (IO Width) => Op (GetScrollbarWidth ()) TextDisplay orig impl 
(~) * impl (IO Int) => Op (GetScrollbarWidth ()) Browser orig impl 
(~) * impl (Int -> IO ()) => Op (SetScrollbarSize ()) Scrolled orig impl 
(~) * impl (Int -> IO ()) => Op (SetScrollbarSize ()) Tree orig impl 
(~) * impl (Int -> IO ()) => Op (SetScrollbarSize ()) Browser orig impl 
(~) * impl (IO Int) => Op (GetScrollbarSize ()) Scrolled orig impl 
(~) * impl (IO Int) => Op (GetScrollbarSize ()) Tree orig impl 
(~) * impl (IO Int) => Op (GetScrollbarSize ()) Browser orig impl 
(~) * impl (ScrollbarMode -> IO ()) => Op (SetHasScrollbar ()) Browser orig impl 
(~) * impl (IO ScrollbarMode) => Op (GetHasScrollbar ()) Browser orig impl 
(~) * impl (Int -> IO ()) => Op (SetHposition ()) Browser orig impl 
(~) * impl (IO Int) => Op (GetHposition ()) Browser orig impl 
(~) * impl (TreeItemLocator -> Bool -> IO ()) => Op (DeselectAndCallback ()) Tree orig impl 
(~) * impl (Int -> IO Int) => Op (DeselectAndCallback ()) Browser orig impl 
(~) * impl (TreeItemLocator -> IO Int) => Op (Deselect ()) Tree orig impl 
(~) * impl (IO ()) => Op (Deselect ()) TreeItem orig impl 
(~) * impl (IO Int) => Op (Deselect ()) Browser orig impl 
(~) * impl (Ref TreeItem -> Bool -> IO ()) => Op (SelectOnlyAndCallback ()) Tree orig impl 
(~) * impl (Ref TreeItem -> IO ()) => Op (SelectOnly ()) Tree orig impl 
(~) * impl (Int -> IO ()) => Op (RemoveIcon ()) Browser orig impl 
(~) * impl (Int -> IO ()) => Op (MakeVisible ()) Browser orig impl 
(~) * impl (Ref TreeItem -> IO Bool) => Op (Displayed ()) Tree orig impl 
(~) * impl (Int -> IO Bool) => Op (Displayed ()) Browser orig impl 
(~) * impl ([Int] -> IO ()) => Op (SetColumnWidths ()) Browser orig impl 
(~) * impl (IO [Int]) => Op (GetColumnWidths ()) Browser orig impl 
(~) * impl (Char -> IO ()) => Op (SetColumnChar ()) Browser orig impl 
(~) * impl (IO Char) => Op (GetColumnChar ()) Browser orig impl 
(~) * impl (Char -> IO ()) => Op (SetFormatChar ()) Browser orig impl 
(~) * impl (IO Char) => Op (GetFormatChar ()) Browser orig impl 
(~) * impl (String -> IO ()) => Op (SetText ()) TextBuffer orig impl 
(~) * impl (Int -> String -> IO ()) => Op (SetText ()) Browser orig impl 
(~) * impl (Int -> IO ()) => Op (HideLine ()) Browser orig impl 
(~) * impl (Int -> IO ()) => Op (ShowWidgetLine ()) Browser orig impl 
(~) * impl (IO Bool) => Op (Selected ()) TextBuffer orig impl 
(~) * impl (IO Bool) => Op (Selected ()) TextSelection orig impl 
(~) * impl (Int -> IO Bool) => Op (Selected ()) Browser orig impl 
(~) * impl (BufferRange -> IO ()) => Op (Select ()) TextBuffer orig impl 
(~) * impl (TreeItemLocator -> IO Int) => Op (Select ()) Tree orig impl 
(~) * impl (IO ()) => Op (Select ()) TreeItem orig impl 
(~) * impl (Int -> Bool -> IO Int) => Op (Select ()) Browser orig impl 
(~) * impl (Int -> IO ()) => Op (SetMiddleline ()) Browser orig impl 
(~) * impl (Int -> IO ()) => Op (SetBottomline ()) Browser orig impl 
(~) * impl (Int -> IO ()) => Op (SetTopline ()) Browser orig impl 
(~) * impl (Int -> LinePosition -> IO ()) => Op (Lineposition ()) Browser orig impl 
(~) * impl (IO Int) => Op (GetTopline ()) Browser orig impl 
(~) * impl (Int -> Int -> IO ()) => Op (Swap ()) Browser orig impl 
(~) * impl (String -> FileSortF -> IO (Either UnknownError ())) => Op (Load ()) FileBrowser orig impl 
(~) * impl (String -> IO Int) => Op (Load ()) Browser orig impl 
(~) * impl (Int -> Int -> IO (Either OutOfRange ())) => Op (Move ()) TreeItem orig impl 
(~) * impl (Int -> Int -> IO ()) => Op (Move ()) Browser orig impl 
(~) * impl (IO ()) => Op (MakeOverlayCurrent ()) GlWindow orig impl 
(~) * impl (IO ()) => Op (HideOverlay ()) GlWindow orig impl 
(~) * impl (IO ()) => Op (Ortho ()) GlWindow orig impl 
(~) * impl (IO ()) => Op (SwapBuffers ()) GlWindow orig impl 
(~) * impl (Ref GlContext -> Bool -> IO ()) => Op (SetContextWithDestroyFlag ()) GlWindow orig impl 
(~) * impl (Ref GlContext -> IO ()) => Op (SetContext ()) GlWindow orig impl 
(~) * impl (IO (Ref GlContext)) => Op (GetContext ()) GlWindow orig impl 
(~) * impl (IO Int) => Op (CanDo ()) GlWindow orig impl 
(~) * impl (Int -> IO Int) => Op (CanDoWithM ()) GlWindow orig impl 
(~) * impl (Bool -> IO ()) => Op (SetContextValid ()) GlWindow orig impl 
(~) * impl (IO Bool) => Op (GetContextValid ()) GlWindow orig impl 
(~) * impl (IO ()) => Op (Invalidate ()) GlWindow orig impl 
(~) * impl (Bool -> IO ()) => Op (SetValid ()) GlWindow orig impl 
(~) * impl (IO Bool) => Op (GetValid ()) GlWindow orig impl 
(~) * impl (TableRowSelectFlag -> IO ()) => Op (SelectAllRows ()) TableRow orig impl 
(~) * impl (Int -> IO (Either OutOfRange Bool)) => Op (GetRowSelected ()) TableRow orig impl 
(~) * impl (Int -> IO ()) => Op (SetColsSuper ()) TableRow orig impl 
(~) * impl (Int -> IO ()) => Op (SetColsSuper ()) Table orig impl 
(~) * impl (Int -> IO ()) => Op (SetRowsSuper ()) TableRow orig impl 
(~) * impl (Int -> IO ()) => Op (SetRowsSuper ()) Table orig impl 
(~) * impl (IO ()) => Op (ClearSuper ()) TableRow orig impl 
(~) * impl (IO ()) => Op (ClearSuper ()) Table orig impl 
(~) * impl (TableContext -> TableCoordinate -> IO (Maybe Rectangle)) => Op (FindCell ()) Table orig impl 
(~) * impl (IO TableContext) => Op (CallbackContext ()) Table orig impl 
(~) * impl (IO Column) => Op (CallbackCol ()) Table orig impl 
(~) * impl (IO Row) => Op (CallbackRow ()) Table orig impl 
(~) * impl (TableCoordinate -> IO Int) => Op (MoveCursor ()) Table orig impl 
(~) * impl (Int -> Int -> Int -> Int -> IO ()) => Op (SetSelection ()) Table orig impl 
(~) * impl (IO (TableCoordinate, TableCoordinate)) => Op (GetSelection ()) Table orig impl 
(~) * impl (TreeItemLocator -> IO Bool) => Op (IsSelected ()) Tree orig impl 
(~) * impl (IO Bool) => Op (IsSelected ()) TreeItem orig impl 
(~) * impl (TableCoordinate -> IO Bool) => Op (IsSelected ()) Table orig impl 
(~) * impl (IO Row) => Op (GetTopRow ()) Table orig impl 
(~) * impl (Row -> IO ()) => Op (SetTopRow ()) Table orig impl 
(~) * impl (IO Column) => Op (GetColPosition ()) Table orig impl 
(~) * impl (IO Row) => Op (GetRowPosition ()) Table orig impl 
(~) * impl (Column -> IO ()) => Op (SetColPosition ()) Table orig impl 
(~) * impl (Row -> IO ()) => Op (SetRowPosition ()) Table orig impl 
(~) * impl (Int -> IO ()) => Op (SetColWidthAll ()) Table orig impl 
(~) * impl (Int -> IO ()) => Op (SetRowHeightAll ()) Table orig impl 
(~) * impl (Column -> IO Int) => Op (GetColWidth ()) Table orig impl 
(~) * impl (Column -> Int -> IO ()) => Op (SetColWidth ()) Table orig impl 
(~) * impl (Row -> IO Int) => Op (GetRowHeight ()) Table orig impl 
(~) * impl (Row -> Int -> IO ()) => Op (SetRowHeight ()) Table orig impl 
(~) * impl (IO Color) => Op (GetColHeaderColor ()) Table orig impl 
(~) * impl (Color -> IO ()) => Op (SetColHeaderColor ()) Table orig impl 
(~) * impl (IO Color) => Op (GetRowHeaderColor ()) Table orig impl 
(~) * impl (Color -> IO ()) => Op (SetRowHeaderColor ()) Table orig impl 
(~) * impl (IO Int) => Op (GetRowHeaderWidth ()) Table orig impl 
(~) * impl (Int -> IO ()) => Op (SetRowHeaderWidth ()) Table orig impl 
(~) * impl (IO Int) => Op (GetColHeaderHeight ()) Table orig impl 
(~) * impl (Int -> IO ()) => Op (SetColHeaderHeight ()) Table orig impl 
(~) * impl (Bool -> IO ()) => Op (SetColHeader ()) Table orig impl 
(~) * impl (IO Bool) => Op (GetColHeader ()) Table orig impl 
(~) * impl (Bool -> IO ()) => Op (SetRowHeader ()) Table orig impl 
(~) * impl (IO Bool) => Op (GetRowHeader ()) Table orig impl 
(~) * impl (Int -> IO ()) => Op (SetRowResizeMin ()) Table orig impl 
(~) * impl (IO Int) => Op (GetRowResizeMin ()) Table orig impl 
(~) * impl (Int -> IO ()) => Op (SetColResizeMin ()) Table orig impl 
(~) * impl (IO Int) => Op (GetColResizeMin ()) Table orig impl 
(~) * impl (Bool -> IO ()) => Op (SetColResize ()) Table orig impl 
(~) * impl (IO Bool) => Op (GetColResize ()) Table orig impl 
(~) * impl (Bool -> IO ()) => Op (SetRowResize ()) Table orig impl 
(~) * impl (IO Bool) => Op (GetRowResize ()) Table orig impl 
(~) * impl (IO Bool) => Op (IsInteractiveResize ()) Table orig impl 
(~) * impl (IO (TableCoordinate, TableCoordinate)) => Op (GetVisibleCells ()) Table orig impl 
(~) * impl (IO Int) => Op (GetCols ()) Table orig impl 
(~) * impl (Int -> IO ()) => Op (SetCols ()) TableRow orig impl 
(~) * impl (Int -> IO ()) => Op (SetCols ()) Table orig impl 
(~) * impl (IO Int) => Op (GetRows ()) TableRow orig impl 
(~) * impl (IO Int) => Op (GetRows ()) Table orig impl 
(~) * impl (Int -> IO ()) => Op (SetRows ()) TableRow orig impl 
(~) * impl (Int -> IO ()) => Op (SetRows ()) Table orig impl 
(~) * impl (IO Boxtype) => Op (GetTableBox ()) Table orig impl 
(~) * impl (Boxtype -> IO ()) => Op (SetTableBox ()) Table orig impl 
(~) * impl (IO (Maybe (Ref TreeItem))) => Op (Prev ()) Tree orig impl 
(~) * impl (IO (Maybe (Ref TreeItem))) => Op (Prev ()) TreeItem orig impl 
(~) * impl (IO ()) => Op (Prev ()) Wizard orig impl 
(~) * impl (Double -> IO ()) => Op (SetYstep ()) Positioner orig impl 
(~) * impl (Double -> IO ()) => Op (SetXstep ()) Positioner orig impl 
(~) * impl (Double -> Double -> IO ()) => Op (SetYbounds ()) Positioner orig impl 
(~) * impl (Double -> Double -> IO ()) => Op (SetXbounds ()) Positioner orig impl 
(~) * impl (IO Double) => Op (GetYmaximum ()) Positioner orig impl 
(~) * impl (Double -> IO ()) => Op (SetYmaximum ()) Positioner orig impl 
(~) * impl (IO Double) => Op (GetXmaximum ()) Positioner orig impl 
(~) * impl (Double -> IO ()) => Op (SetXmaximum ()) Positioner orig impl 
(~) * impl (IO Double) => Op (GetYminimum ()) Positioner orig impl 
(~) * impl (Double -> IO ()) => Op (SetYminimum ()) Positioner orig impl 
(~) * impl (IO Double) => Op (GetXminimum ()) Positioner orig impl 
(~) * impl (Double -> IO ()) => Op (SetXminimum ()) Positioner orig impl 
(~) * impl (IO Double) => Op (GetYvalue ()) Positioner orig impl 
(~) * impl (Double -> IO ()) => Op (SetYvalue ()) Positioner orig impl 
(~) * impl (IO Double) => Op (GetXvalue ()) Positioner orig impl 
(~) * impl (Double -> IO ()) => Op (SetXvalue ()) Positioner orig impl 
(~) * impl (Bool -> IO ()) => Op (SetSuspended ()) Timer orig impl 
(~) * impl (IO Bool) => Op (GetSuspended ()) Timer orig impl 
(~) * impl (CountDirection -> IO ()) => Op (SetDirection ()) Timer orig impl 
(~) * impl (IO CountDirection) => Op (GetDirection ()) Timer orig impl 
(~) * impl (IO Int) => Op (SetTabNav ()) Input orig impl 
(~) * impl (Int -> IO ()) => Op (GetTabNav ()) Input orig impl 
(~) * impl (Int -> IO ()) => Op (SetWrap ()) Input orig impl 
(~) * impl (IO Int) => Op (GetWrap ()) Input orig impl 
(~) * impl (Int -> IO ()) => Op (SetReadonly ()) Input orig impl 
(~) * impl (IO Int) => Op (GetReadonly ()) Input orig impl 
(~) * impl (Int -> IO ()) => Op (SetInputType ()) Input orig impl 
(~) * impl (IO Int) => Op (GetInputType ()) Input orig impl 
(~) * impl (Color -> IO ()) => Op (SetCursorColor ()) TextDisplay orig impl 
(~) * impl (Color -> IO ()) => Op (SetCursorColor ()) Input orig impl 
(~) * impl (IO Color) => Op (GetCursorColor ()) TextDisplay orig impl 
(~) * impl (IO Color) => Op (GetCursorColor ()) Input orig impl 
(~) * impl (IO (Either NoChange ())) => Op (CopyCuts ()) Input orig impl 
(~) * impl (IO (Either NoChange BufferOffset)) => Op (Undo ()) TextBuffer orig impl 
(~) * impl (IO (Either NoChange ())) => Op (Undo ()) Input orig impl 
(~) * impl (String -> Int -> IO (Either NoChange ())) => Op (InsertWithLength ()) Input orig impl 
(~) * impl (Int -> Int -> IO (Either NoChange ())) => Op (CutRange ()) Input orig impl 
(~) * impl (Int -> IO (Either NoChange ())) => Op (CutFromCursor ()) Input orig impl 
(~) * impl (IO (Either NoChange ())) => Op (Cut ()) Input orig impl 
(~) * impl (Int -> IO (Either NoChange ())) => Op (SetMark ()) Input orig impl 
(~) * impl (Rectangle -> IO ()) => Op (SetPosition ()) Tile orig impl 
(~) * impl (Int -> IO ()) => Op (SetPosition ()) Browser orig impl 
(~) * impl (Int -> Maybe Int -> IO (Either NoChange ())) => Op (SetPosition ()) Input orig impl 
(~) * impl (IO Int) => Op (GetMark ()) Input orig impl 
(~) * impl (IO (Maybe BufferRange)) => Op (GetPosition ()) TextSelection orig impl 
(~) * impl (IO Int) => Op (GetPosition ()) Browser orig impl 
(~) * impl (IO Int) => Op (GetPosition ()) Input orig impl 
(~) * impl (Int -> IO ()) => Op (SetMaximumSize ()) Input orig impl 
(~) * impl (IO Int) => Op (GetMaximumSize ()) Input orig impl 
(~) * impl (Int -> IO Char) => Op (Index ()) Input orig impl 
(~) * impl (String -> Maybe Int -> IO (Either NoChange ())) => Op (StaticValue ()) Input orig impl 
(~) * impl (Int -> Int -> Int -> Int -> IO Int) => Op (SetScrollValue ()) Scrollbar orig impl 
(~) * impl (IO LineSize) => Op (GetLinesize ()) Scrollbar orig impl 
(~) * impl (LineSize -> IO ()) => Op (SetLinesize ()) Scrollbar orig impl 
(~) * impl (Double -> IO ()) => Op (SetLstep ()) Counter orig impl 
(~) * impl (Angle -> Angle -> IO ()) => Op (SetAngles ()) Dial orig impl 
(~) * impl (Angle -> IO ()) => Op (SetAngle2 ()) Dial orig impl 
(~) * impl (IO Angle) => Op (GetAngle2 ()) Dial orig impl 
(~) * impl (Angle -> IO ()) => Op (SetAngle1 ()) Dial orig impl 
(~) * impl (IO Angle) => Op (GetAngle1 ()) Dial orig impl 
(~) * impl (IO Bool) => Op (GetSoft ()) ValueOutput orig impl 
(~) * impl (IO Bool) => Op (GetSoft ()) ValueInput orig impl 
(~) * impl (IO Int) => Op (GetSoft ()) Adjuster orig impl 
(~) * impl (Bool -> IO ()) => Op (SetSoft ()) ValueOutput orig impl 
(~) * impl (Bool -> IO ()) => Op (SetSoft ()) ValueInput orig impl 
(~) * impl (Int -> IO ()) => Op (SetSoft ()) Adjuster orig impl 
(~) * impl (IO ()) => Op (SetCurrent ()) ImageSurface orig impl 
(~) * impl (IO ()) => Op (SetCurrent ()) CopySurface orig impl 
(~) * impl (IO String) => Op (ClassName ()) ImageSurface orig impl 
(~) * impl (IO String) => Op (ClassName ()) Image orig impl 
(~) * impl (IO ()) => Op (Uncache ()) RGBImage orig impl 
(~) * impl (IO ()) => Op (Uncache ()) Pixmap orig impl 
(~) * impl (IO ()) => Op (Uncache ()) Bitmap orig impl 
(~) * impl (IO ()) => Op (Uncache ()) Image orig impl 
(~) * impl (Position -> Size -> Maybe X -> Maybe Y -> IO ()) => Op (DrawResize ()) RGBImage orig impl 
(~) * impl (Position -> Size -> Maybe X -> Maybe Y -> IO ()) => Op (DrawResize ()) Pixmap orig impl 
(~) * impl (Position -> Size -> Maybe X -> Maybe Y -> IO ()) => Op (DrawResize ()) Bitmap orig impl 
(~) * impl (Position -> Size -> Maybe X -> Maybe Y -> IO ()) => Op (DrawResize ()) Image orig impl 
(~) * impl (IO ()) => Op (Desaturate ()) RGBImage orig impl 
(~) * impl (IO ()) => Op (Desaturate ()) Pixmap orig impl 
(~) * impl (IO ()) => Op (Desaturate ()) Bitmap orig impl 
(~) * impl (IO ()) => Op (Desaturate ()) Image orig impl 
(~) * impl (IO ()) => Op (Inactive ()) RGBImage orig impl 
(~) * impl (IO ()) => Op (Inactive ()) Pixmap orig impl 
(~) * impl (IO ()) => Op (Inactive ()) Bitmap orig impl 
(~) * impl (IO ()) => Op (Inactive ()) Image orig impl 
(~) * impl (Color -> Float -> IO ()) => Op (ColorAverage ()) RGBImage orig impl 
(~) * impl (Color -> Float -> IO ()) => Op (ColorAverage ()) Pixmap orig impl 
(~) * impl (Color -> Float -> IO ()) => Op (ColorAverage ()) Bitmap orig impl 
(~) * impl (Color -> Float -> IO ()) => Op (ColorAverage ()) Image orig impl 
(~) * impl (IO Int) => Op (GetCount ()) RGBImage orig impl 
(~) * impl (IO Int) => Op (GetCount ()) NativeFileChooser orig impl 
(~) * impl (IO Int) => Op (GetCount ()) Pixmap orig impl 
(~) * impl (IO Int) => Op (GetCount ()) Bitmap orig impl 
(~) * impl (IO Int) => Op (GetCount ()) Image orig impl 
(~) * impl (IO Int) => Op (GetLd ()) RGBImage orig impl 
(~) * impl (IO Int) => Op (GetLd ()) Pixmap orig impl 
(~) * impl (IO Int) => Op (GetLd ()) Bitmap orig impl 
(~) * impl (IO Int) => Op (GetLd ()) Image orig impl 
(~) * impl (IO Int) => Op (GetD ()) RGBImage orig impl 
(~) * impl (IO Int) => Op (GetD ()) Pixmap orig impl 
(~) * impl (IO Int) => Op (GetD ()) Bitmap orig impl 
(~) * impl (IO Int) => Op (GetD ()) Image orig impl 
(~) * impl (Color -> IO ()) => Op (SetTextcolor ()) Spinner orig impl 
(~) * impl (Color -> IO ()) => Op (SetTextcolor ()) TextDisplay orig impl 
(~) * impl (Color -> IO ()) => Op (SetTextcolor ()) Browser orig impl 
(~) * impl (Color -> IO ()) => Op (SetTextcolor ()) ValueOutput orig impl 
(~) * impl (Color -> IO ()) => Op (SetTextcolor ()) ValueInput orig impl 
(~) * impl (Color -> IO ()) => Op (SetTextcolor ()) Input orig impl 
(~) * impl (Color -> IO ()) => Op (SetTextcolor ()) ValueSlider orig impl 
(~) * impl (Color -> IO ()) => Op (SetTextcolor ()) Counter orig impl 
(~) * impl (Color -> IO ()) => Op (SetTextcolor ()) MenuPrim orig impl 
(~) * impl (IO Color) => Op (GetTextcolor ()) Spinner orig impl 
(~) * impl (IO Color) => Op (GetTextcolor ()) TextDisplay orig impl 
(~) * impl (IO Color) => Op (GetTextcolor ()) Browser orig impl 
(~) * impl (IO Color) => Op (GetTextcolor ()) ValueOutput orig impl 
(~) * impl (IO Color) => Op (GetTextcolor ()) ValueInput orig impl 
(~) * impl (IO Color) => Op (GetTextcolor ()) Input orig impl 
(~) * impl (IO Color) => Op (GetTextcolor ()) ValueSlider orig impl 
(~) * impl (IO Color) => Op (GetTextcolor ()) Counter orig impl 
(~) * impl (IO Color) => Op (GetTextcolor ()) MenuPrim orig impl 
(~) * impl (FontSize -> IO ()) => Op (SetTextsize ()) FileBrowser orig impl 
(~) * impl (FontSize -> IO ()) => Op (SetTextsize ()) Spinner orig impl 
(~) * impl (FontSize -> IO ()) => Op (SetTextsize ()) TextDisplay orig impl 
(~) * impl (FontSize -> IO ()) => Op (SetTextsize ()) Browser orig impl 
(~) * impl (FontSize -> IO ()) => Op (SetTextsize ()) ValueOutput orig impl 
(~) * impl (FontSize -> IO ()) => Op (SetTextsize ()) ValueInput orig impl 
(~) * impl (FontSize -> IO ()) => Op (SetTextsize ()) Input orig impl 
(~) * impl (FontSize -> IO ()) => Op (SetTextsize ()) ValueSlider orig impl 
(~) * impl (FontSize -> IO ()) => Op (SetTextsize ()) Counter orig impl 
(~) * impl (FontSize -> IO ()) => Op (SetTextsize ()) MenuPrim orig impl 
(~) * impl (IO FontSize) => Op (GetTextsize ()) FileBrowser orig impl 
(~) * impl (IO FontSize) => Op (GetTextsize ()) Spinner orig impl 
(~) * impl (IO FontSize) => Op (GetTextsize ()) TextDisplay orig impl 
(~) * impl (IO FontSize) => Op (GetTextsize ()) Browser orig impl 
(~) * impl (IO FontSize) => Op (GetTextsize ()) ValueOutput orig impl 
(~) * impl (IO FontSize) => Op (GetTextsize ()) ValueInput orig impl 
(~) * impl (IO FontSize) => Op (GetTextsize ()) Input orig impl 
(~) * impl (IO FontSize) => Op (GetTextsize ()) ValueSlider orig impl 
(~) * impl (IO FontSize) => Op (GetTextsize ()) Counter orig impl 
(~) * impl (IO FontSize) => Op (GetTextsize ()) MenuPrim orig impl 
(~) * impl (Font -> IO ()) => Op (SetTextfont ()) Spinner orig impl 
(~) * impl (Font -> IO ()) => Op (SetTextfont ()) TextDisplay orig impl 
(~) * impl (Font -> IO ()) => Op (SetTextfont ()) Browser orig impl 
(~) * impl (Font -> IO ()) => Op (SetTextfont ()) ValueOutput orig impl 
(~) * impl (Font -> IO ()) => Op (SetTextfont ()) ValueInput orig impl 
(~) * impl (Font -> IO ()) => Op (SetTextfont ()) Input orig impl 
(~) * impl (Font -> IO ()) => Op (SetTextfont ()) ValueSlider orig impl 
(~) * impl (Font -> IO ()) => Op (SetTextfont ()) Counter orig impl 
(~) * impl (Font -> IO ()) => Op (SetTextfont ()) MenuPrim orig impl 
(~) * impl (IO Font) => Op (GetTextfont ()) Spinner orig impl 
(~) * impl (IO Font) => Op (GetTextfont ()) TextDisplay orig impl 
(~) * impl (IO Font) => Op (GetTextfont ()) Browser orig impl 
(~) * impl (IO Font) => Op (GetTextfont ()) ValueOutput orig impl 
(~) * impl (IO Font) => Op (GetTextfont ()) ValueInput orig impl 
(~) * impl (IO Font) => Op (GetTextfont ()) Input orig impl 
(~) * impl (IO Font) => Op (GetTextfont ()) ValueSlider orig impl 
(~) * impl (IO Font) => Op (GetTextfont ()) Counter orig impl 
(~) * impl (IO Font) => Op (GetTextfont ()) MenuPrim orig impl 
(~) * impl (Int -> IO String) => Op (GetTextWithIndex ()) MenuPrim orig impl 
(~) * impl (IO String) => Op (GetText ()) TextBuffer orig impl 
(~) * impl (Int -> IO String) => Op (GetText ()) Browser orig impl 
(~) * impl (IO String) => Op (GetText ()) MenuPrim orig impl 
(~) * impl (IO String) => Op (GetText ()) MenuItem orig impl 
(~) * impl (IO (Maybe (Ref MenuItem))) => Op (Mvalue ()) MenuPrim orig impl 
(~) * impl (IO ColorChooserMode) => Op (GetMode ()) ColorChooser orig impl 
(~) * impl (IO Mode) => Op (GetMode ()) GlWindow orig impl 
(~) * impl (Int -> IO Int) => Op (GetMode ()) SysMenuBar orig impl 
(~) * impl (Int -> IO Int) => Op (GetMode ()) MenuPrim orig impl 
(~) * impl (ColorChooserMode -> IO ()) => Op (SetMode ()) ColorChooser orig impl 
(~) * impl (Mode -> IO Int) => Op (SetMode ()) GlWindow orig impl 
(~) * impl (Int -> Int -> IO ()) => Op (SetMode ()) SysMenuBar orig impl 
(~) * impl (Int -> MenuItemFlags -> IO ()) => Op (SetMode ()) MenuPrim orig impl 
(~) * impl (BufferRange -> IO ()) => Op (Remove ()) TextBuffer orig impl 
(~) * impl (Ref TreeItem -> IO (Either TreeItemNotFound ())) => Op (Remove ()) Tree orig impl 
(~) * impl (Int -> IO ()) => Op (Remove ()) Browser orig impl 
(~) * impl (Int -> IO ()) => Op (Remove ()) SysMenuBar orig impl 
(~) * impl (Int -> IO ()) => Op (Remove ()) MenuPrim orig impl 
(~) * impl (BufferRange -> String -> IO ()) => Op (Replace ()) TextBuffer orig impl 
(~) * impl (Int -> Int -> String -> IO (Either NoChange ())) => Op (Replace ()) Input orig impl 
(~) * impl (Int -> String -> IO ()) => Op (Replace ()) SysMenuBar orig impl 
(~) * impl (Int -> String -> IO ()) => Op (Replace ()) MenuPrim orig impl 
(~) * impl (String -> IO ()) => Op (AddName ()) MenuPrim orig impl 
(~) * impl (Int -> IO Int) => Op (ClearSubmenu ()) SysMenuBar orig impl 
(~) * impl (Int -> IO (Either OutOfRange ())) => Op (ClearSubmenu ()) MenuPrim orig impl 
(~) * impl (Int -> Int -> IO ()) => Op (SetSize ()) Browser orig impl 
(~) * impl (Size -> IO ()) => Op (SetSize ()) Input orig impl 
(~) * impl (Int -> Int -> IO ()) => Op (SetSize ()) MenuPrim orig impl 
(Parent a RGBImage, (~) * impl (Maybe Size -> IO (Maybe (Ref a)))) => Op (Copy ()) RGBImage orig impl 
(Parent a TextBuffer, (~) * impl (Ref a -> BufferRange -> BufferOffset -> IO ())) => Op (Copy ()) TextBuffer orig impl 
(~) * impl (Clipboard -> IO (Either NoChange ())) => Op (Copy ()) Input orig impl 
(~) * impl (Maybe Size -> IO (Maybe (Ref Pixmap))) => Op (Copy ()) Pixmap orig impl 
(~) * impl (Maybe Size -> IO (Maybe (Ref Bitmap))) => Op (Copy ()) Bitmap orig impl 
(~) * impl (Maybe Size -> IO (Maybe (Ref Image))) => Op (Copy ()) Image orig impl 
(Parent a MenuItem, (~) * impl (Ref a -> IO ())) => Op (Copy ()) MenuPrim orig impl 
(~) * impl ([Ref MenuItem] -> IO ()) => Op (SetMenu ()) SysMenuBar orig impl 
(Parent a MenuItem, (~) * impl ([Ref a] -> IO ())) => Op (SetMenu ()) MenuPrim orig impl 
(~) * impl (IO [Maybe (Ref MenuItem)]) => Op (GetMenu ()) MenuPrim orig impl 
(~) * impl (IO ()) => Op (Global ()) SysMenuBar orig impl 
(~) * impl (IO ()) => Op (Global ()) MenuPrim orig impl 
(~) * impl (MenuItemLocator -> IO (Maybe Int)) => Op (FindIndex ()) MenuPrim orig impl 
(Parent a MenuItem, Parent b MenuItem, (~) * impl (Ref a -> IO (Maybe (Ref b)))) => Op (Picked ()) MenuPrim orig impl 
(~) * impl (IO (Maybe String)) => Op (ItemPathnameRecent ()) MenuPrim orig impl 
(Parent a TreeItem, (~) * impl (Ref a -> IO (Maybe String))) => Op (ItemPathname ()) Tree orig impl 
(Parent a MenuItem, (~) * impl (Ref a -> IO (Maybe String))) => Op (ItemPathname ()) MenuPrim orig impl 
(~) * impl (IO Int) => Op (GetSize ()) Browser orig impl 
(~) * impl (IO Int) => Op (GetSize ()) Input orig impl 
(~) * impl (IO Int) => Op (GetSize ()) MenuPrim orig impl 
(~) * impl (IO Int) => Op (GetSize ()) MenuItem orig impl 
(~) * impl (TableContext -> TableCoordinate -> IO ()) => Op (DoCallback ()) Table orig impl 
(~) * impl (Ref Widget -> IO ()) => Op (DoCallback ()) MenuItem orig impl 
(~) * impl (IO ()) => Op (DoCallback ()) Widget orig impl 
(Parent a MenuItem, (~) * impl (Maybe Int -> Bool -> IO (Maybe (Ref a)))) => Op (FindShortcut ()) MenuItem orig impl 
(Parent a MenuItem, (~) * impl (IO (Maybe (Ref a)))) => Op (TestShortcut ()) MenuPrim orig impl 
(Parent a MenuItem, (~) * impl (IO (Maybe (Ref a)))) => Op (TestShortcut ()) MenuItem orig impl 
(~) * impl (IO (Maybe (Ref MenuItem))) => Op (Popup ()) MenuButton orig impl 
(Parent a MenuItem, Parent b MenuPrim, Parent c MenuItem, (~) * impl (Position -> Maybe String -> Maybe (Ref a) -> Maybe (Ref b) -> IO (Maybe (Ref c)))) => Op (Popup ()) MenuItem orig impl 
(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 
(~) * impl (MenuItemFlags -> IO ()) => Op (SetFlags ()) MenuItem orig impl 
(~) * impl (IO (Maybe MenuItemFlags)) => Op (GetFlags ()) MenuItem orig impl 
(~) * impl (Position -> IO ()) => Op (Draw ()) RGBImage orig impl 
(~) * impl (IO ()) => Op (Draw ()) Tree orig impl 
(~) * impl (IO ()) => Op (Draw ()) Table orig impl 
(Parent a Widget, (~) * impl (Ref a -> Position -> IO ())) => Op (Draw ()) ImageSurface orig impl 
(Parent a Widget, (~) * impl (Ref a -> Position -> IO ())) => Op (Draw ()) CopySurface orig impl 
(~) * impl (Position -> IO ()) => Op (Draw ()) Pixmap orig impl 
(~) * impl (Position -> IO ()) => Op (Draw ()) Bitmap orig impl 
(~) * impl (Position -> IO ()) => Op (Draw ()) Image orig impl 
(Parent a MenuPrim, (~) * impl (Rectangle -> Ref a -> IO ())) => Op (Draw ()) MenuItem orig impl 
(Parent a MenuPrim, (~) * impl (Rectangle -> Ref a -> Int -> IO ())) => Op (DrawWithT ()) MenuItem orig impl 
(Parent a MenuPrim, (~) * impl (Ref a -> IO Size)) => Op (Measure ()) MenuItem orig impl 
(~) * impl (IO Bool) => Op (Activevisible ()) MenuItem orig impl 
(~) * impl (IO Bool) => Op (Visible ()) TreeItem orig impl 
(~) * impl (Int -> IO Int) => Op (Visible ()) Browser orig impl 
(~) * impl (IO Bool) => Op (Visible ()) MenuItem orig impl 
(~) * impl (IO Bool) => Op (Radio ()) MenuItem orig impl 
(~) * impl (IO Bool) => Op (Checkbox ()) MenuItem orig impl 
(~) * impl (IO Bool) => Op (Submenu ()) MenuItem orig impl 
(~) * impl (Labeltype -> String -> IO ()) => Op (SetLabelWithLabeltype ()) MenuItem orig impl 
(~) * impl (IO (Maybe (Ref TreeItem))) => Op (GetFirst ()) Tree orig impl 
(~) * impl (IO (Maybe (Ref MenuItem))) => Op (GetFirst ()) MenuItem orig impl 
(~) * impl (IO (Maybe (Ref TreeItem))) => Op (Next ()) Tree orig impl 
(~) * impl (IO (Maybe (Ref TreeItem))) => Op (Next ()) TreeItem orig impl 
(~) * impl (IO ()) => Op (Next ()) Wizard orig impl 
(~) * impl (IO (Maybe (Ref MenuItem))) => Op (Next ()) MenuItem orig impl 
(Parent a MenuItem, (~) * impl (Int -> IO (Maybe (Ref a)))) => Op (NextWithStep ()) MenuItem orig impl 
(~) * impl (Boxtype -> IO ()) => Op (SetSlider ()) Slider orig impl 
(~) * impl (IO Boxtype) => Op (GetSlider ()) Slider orig impl 
(~) * impl (Double -> IO ()) => Op (GetSliderSize ()) Slider orig impl 
(~) * impl (IO Float) => Op (SetSliderSize ()) Slider orig impl 
(~) * impl (Int -> Int -> Int -> Int -> IO Int) => Op (Scrollvalue ()) Slider orig impl 
(~) * impl (Double -> Int -> IO Double) => Op (Increment ()) Valuator orig impl 
(~) * impl (Double -> IO Double) => Op (Clamp ()) Valuator orig impl 
(~) * impl (Double -> IO Double) => Op (Round ()) Valuator orig impl 
(~) * impl (String -> IO ()) => Op (SetFormat ()) Spinner orig impl 
(~) * impl (String -> IO Int) => Op (SetFormat ()) Valuator orig impl 
(~) * impl (Int -> IO ()) => Op (Precision ()) Valuator orig impl 
(~) * impl (IO Double) => Op (GetStep ()) Spinner orig impl 
(~) * impl (IO Rational) => Op (GetStep ()) Valuator orig impl 
(~) * impl (Double -> IO ()) => Op (SetStep ()) Spinner orig impl 
(~) * impl (Rational -> IO ()) => Op (SetStep ()) Valuator orig impl 
(~) * impl (Double -> Double -> IO ()) => Op (Range ()) Spinner orig impl 
(~) * impl (Double -> Double -> IO ()) => Op (Range ()) Valuator orig impl 
(~) * impl (Double -> IO ()) => Op (SetMaximum ()) Spinner orig impl 
(~) * impl (Float -> IO ()) => Op (SetMaximum ()) Progress orig impl 
(~) * impl (Double -> IO ()) => Op (SetMaximum ()) Valuator orig impl 
(~) * impl (IO Double) => Op (GetMaximum ()) Spinner orig impl 
(~) * impl (IO Float) => Op (GetMaximum ()) Progress orig impl 
(~) * impl (IO Double) => Op (GetMaximum ()) Valuator orig impl 
(~) * impl (Double -> IO ()) => Op (SetMinimum ()) Spinner orig impl 
(~) * impl (Float -> IO ()) => Op (SetMinimum ()) Progress orig impl 
(~) * impl (Double -> IO ()) => Op (SetMinimum ()) Valuator orig impl 
(~) * impl (IO Double) => Op (GetMinimum ()) Spinner orig impl 
(~) * impl (IO Float) => Op (GetMinimum ()) Progress orig impl 
(~) * impl (IO Double) => Op (GetMinimum ()) Valuator orig impl 
(~) * impl (Double -> Double -> IO ()) => Op (Bounds ()) Slider orig impl 
(~) * impl (Double -> Double -> IO ()) => Op (Bounds ()) Valuator orig impl 
(~) * impl (Int -> IO ()) => Op (SetDownColor ()) MenuPrim orig impl 
(~) * impl (Color -> IO ()) => Op (SetDownColor ()) Button orig impl 
(~) * impl (IO Color) => Op (GetDownColor ()) MenuPrim orig impl 
(~) * impl (IO Color) => Op (GetDownColor ()) Button orig impl 
(~) * impl (Boxtype -> IO ()) => Op (SetDownBox ()) MenuPrim orig impl 
(~) * impl (Boxtype -> IO ()) => Op (SetDownBox ()) Button orig impl 
(~) * impl (IO Boxtype) => Op (GetDownBox ()) MenuPrim orig impl 
(~) * impl (IO Boxtype) => Op (GetDownBox ()) Button orig impl 
(~) * impl (ShortcutKeySequence -> IO ()) => Op (SetShortcut ()) TextDisplay orig impl 
(~) * impl (ShortcutKeySequence -> IO ()) => Op (SetShortcut ()) ValueInput orig impl 
(~) * impl (ShortcutKeySequence -> IO ()) => Op (SetShortcut ()) Input orig impl 
(~) * impl (Int -> ShortcutKeySequence -> IO ()) => Op (SetShortcut ()) SysMenuBar orig impl 
(~) * impl (Int -> ShortcutKeySequence -> IO ()) => Op (SetShortcut ()) MenuPrim orig impl 
(~) * impl (ShortcutKeySequence -> IO ()) => Op (SetShortcut ()) MenuItem orig impl 
(~) * impl (ShortcutKeySequence -> IO ()) => Op (SetShortcut ()) Button orig impl 
(~) * impl (IO (Maybe ShortcutKeySequence)) => Op (GetShortcut ()) TextDisplay orig impl 
(~) * impl (IO (Maybe ShortcutKeySequence)) => Op (GetShortcut ()) ValueInput orig impl 
(~) * impl (IO (Maybe ShortcutKeySequence)) => Op (GetShortcut ()) Input orig impl 
(~) * impl (IO (Maybe ShortcutKeySequence)) => Op (GetShortcut ()) MenuItem orig impl 
(~) * impl (IO (Maybe ShortcutKeySequence)) => Op (GetShortcut ()) Button orig impl 
(~) * impl (IO ()) => Op (Setonly ()) MenuItem orig impl 
(~) * impl (IO ()) => Op (Setonly ()) Button orig impl 
(~) * impl (BufferRange -> IO ()) => Op (Set ()) TextSelection orig impl 
(~) * impl (IO ()) => Op (Set ()) MenuItem orig impl 
(~) * impl (IO Bool) => Op (Set ()) Button orig impl 
(~) * impl (Double -> IO ()) => Op (SetValue ()) Spinner orig impl 
(Parent a Widget, (~) * impl (Maybe (Ref a) -> IO (Either NoChange ()))) => Op (SetValue ()) Tabs orig impl 
(~) * impl (ClockSetTimeType -> IO ()) => Op (SetValue ()) Clock orig impl 
(~) * impl (Int -> IO ()) => Op (SetValue ()) Browser orig impl 
(Parent a Widget, (~) * impl (Maybe (Ref a) -> IO ())) => Op (SetValue ()) Wizard orig impl 
(~) * impl (Float -> IO ()) => Op (SetValue ()) Progress orig impl 
(~) * impl (Double -> IO ()) => Op (SetValue ()) Timer orig impl 
(~) * impl (String -> Maybe Int -> IO Int) => Op (SetValue ()) Input orig impl 
(~) * impl (MenuItemReference -> IO Int) => Op (SetValue ()) Choice orig impl 
(~) * impl (MenuItemReference -> IO Int) => Op (SetValue ()) MenuPrim orig impl 
(~) * impl (Double -> IO Int) => Op (SetValue ()) Valuator orig impl 
(~) * impl (Bool -> IO Bool) => Op (SetValue ()) Button orig impl 
(~) * impl (IO (Either OutOfRange Between0And1)) => Op (GetValue ()) ColorChooser orig impl 
(~) * impl (IO Double) => Op (GetValue ()) Spinner orig impl 
(~) * impl (IO (Maybe (Ref Widget))) => Op (GetValue ()) Tabs orig impl 
(~) * impl (IO ClockByTime) => Op (GetValue ()) Clock orig impl 
(~) * impl (IO Int) => Op (GetValue ()) Browser orig impl 
(~) * impl (IO (Maybe (Ref Widget))) => Op (GetValue ()) Wizard orig impl 
(~) * impl (IO Float) => Op (GetValue ()) Progress orig impl 
(~) * impl (IO Double) => Op (GetValue ()) Timer orig impl 
(~) * impl (IO String) => Op (GetValue ()) Input orig impl 
(~) * impl (IO MenuItemIndex) => Op (GetValue ()) Choice orig impl 
(~) * impl (IO MenuItemIndex) => Op (GetValue ()) MenuPrim orig impl 
(~) * impl (IO Int) => Op (GetValue ()) MenuItem orig impl 
(~) * impl (IO Double) => Op (GetValue ()) Valuator orig impl 
(~) * impl (IO Bool) => Op (GetValue ()) Button orig impl 
(~) * impl (IO ()) => Op (Flush ()) GlWindow orig impl 
(~) * impl (IO ()) => Op (Flush ()) OverlayWindow orig impl 
(~) * impl (IO ()) => Op (RedrawOverlay ()) GlWindow orig impl 
(~) * impl (IO ()) => Op (RedrawOverlay ()) OverlayWindow orig impl 
(~) * impl (IO Int) => Op (CanDoOverlay ()) GlWindow orig impl 
(~) * impl (IO Int) => Op (CanDoOverlay ()) OverlayWindow orig impl 
(~) * impl (IO ()) => Op (WaitForExpose ()) Window orig impl 
(~) * impl (IO Int) => Op (GetDecoratedH ()) Window orig impl 
(~) * impl (IO Int) => Op (GetDecoratedW ()) Window orig impl 
(~) * impl (CursorType -> (Maybe Color, Maybe Color) -> IO ()) => Op (SetDefaultCursorWithFgBg ()) Window orig impl 
(~) * impl (CursorType -> IO ()) => Op (SetDefaultCursor ()) Window orig impl 
(~) * impl (Cursor -> (Maybe Color, Maybe Color) -> IO ()) => Op (SetCursorWithFgBg ()) Window orig impl 
(~) * impl (Cursor -> IO ()) => Op (SetCursor ()) Window orig impl 
(~) * impl (IO ()) => Op (MakeCurrent ()) Window orig impl 
(~) * impl (IO Int) => Op (GetYRoot ()) Window orig impl 
(~) * impl (IO Int) => Op (GetXRoot ()) Window orig impl 
(~) * impl (IO ()) => Op (Iconize ()) Window orig impl 
(~) * impl (IO Bool) => Op (Shown ()) Window orig impl 
(~) * impl (Int -> Ref Image -> IO ()) => Op (SetIcon ()) Browser orig impl 
(Parent a Image, (~) * impl (Maybe (Ref a) -> IO ())) => Op (SetIcon ()) Window orig impl 
(~) * impl (Int -> IO (Maybe (Ref Image))) => Op (GetIcon ()) Browser orig impl 
(~) * impl (IO (Maybe (Ref Image))) => Op (GetIcon ()) Window orig impl 
(~) * impl (String -> IO ()) => Op (SetXclass ()) Window orig impl 
(~) * impl (IO String) => Op (GetXclass ()) Window orig impl 
(~) * impl (String -> String -> IO ()) => Op (SetLabelWithIconlabel ()) Window orig impl 
(~) * impl (String -> IO ()) => Op (SetIconlabel ()) Window orig impl 
(~) * impl (IO String) => Op (GetIconlabel ()) Window orig impl 
(~) * impl (Int -> Int -> OptionalSizeRangeArgs -> IO ()) => Op (SizeRangeWithArgs ()) Window orig impl 
(~) * impl (Int -> Int -> IO ()) => Op (SizeRange ()) Window orig impl 
(~) * impl (IO ()) => Op (FreePosition ()) Window orig impl 
(~) * impl (PositionSpec -> Maybe Bool -> IO ()) => Op (HotSpot ()) Window orig impl 
(~) * impl (IO Bool) => Op (GetTooltipWindow ()) Window orig impl 
(~) * impl (IO ()) => Op (SetTooltipWindow ()) Window orig impl 
(~) * impl (IO Bool) => Op (GetMenuWindow ()) Window orig impl 
(~) * impl (IO ()) => Op (SetMenuWindow ()) Window orig impl 
(~) * impl (IO Bool) => Op (NonModal ()) Window orig impl 
(~) * impl (IO ()) => Op (SetNonModal ()) Window orig impl 
(~) * impl (IO Bool) => Op (GetModal ()) Window orig impl 
(~) * impl (IO ()) => Op (SetModal ()) Window orig impl 
(~) * impl (IO Bool) => Op (GetOverride ()) Window orig impl 
(~) * impl (IO ()) => Op (SetOverride ()) Window orig impl 
(~) * impl (IO Bool) => Op (GetBorder ()) Window orig impl 
(~) * impl (IO ()) => Op (ClearBorder ()) Window orig impl 
(~) * impl (Bool -> IO ()) => Op (SetBorder ()) Window orig impl 
(~) * impl (Maybe Rectangle -> IO ()) => Op (FullscreenOff ()) Window orig impl 
(~) * impl (IO ()) => Op (MakeFullscreen ()) Window orig impl 
(~) * impl (IO Bool) => Op (Changed ()) Window orig impl 
(~) * impl (IO Bool) => Op (Changed ()) Widget orig impl 
(~) * impl (IO ()) => Op (FlushSuper ()) GlWindow orig impl 
(~) * impl (IO ()) => Op (FlushSuper ()) DoubleWindow orig impl 
(~) * impl (IO ()) => Op (FlushSuper ()) SingleWindow orig impl 
(~) * impl (IO ()) => Op (FlushSuper ()) Window orig impl 
(~) * impl (Event -> IO Int) => Op (HandleSuper ()) GlWindow orig impl 
(~) * impl (Int -> IO Int) => Op (HandleSuper ()) MenuPrim orig impl 
(~) * impl (Int -> IO Int) => Op (HandleSuper ()) Button orig impl 
(~) * impl (Int -> IO Int) => Op (HandleSuper ()) DoubleWindow orig impl 
(~) * impl (Int -> IO Int) => Op (HandleSuper ()) SingleWindow orig impl 
(~) * impl (Int -> IO Int) => Op (HandleSuper ()) Window orig impl 
(~) * impl (IO ()) => Op (DrawSuper ()) GlWindow orig impl 
(~) * impl (IO ()) => Op (DrawSuper ()) Table orig impl 
(~) * impl (IO ()) => Op (DrawSuper ()) Button orig impl 
(~) * impl (IO ()) => Op (DrawSuper ()) DoubleWindow orig impl 
(~) * impl (IO ()) => Op (DrawSuper ()) SingleWindow orig impl 
(~) * impl (IO ()) => Op (DrawSuper ()) Window orig impl 
(~) * impl (Int -> IO (Maybe (Ref Widget))) => Op (GetChild ()) Table orig impl 
(~) * impl (Int -> IO (Maybe (Ref Widget))) => Op (GetChild ()) Group orig impl 
(~) * impl (IO [Ref Widget]) => Op (GetArray ()) Table orig impl 
(~) * impl (IO [Ref Widget]) => Op (GetArray ()) Group orig impl 
(Parent a Widget, Parent b Widget, (~) * impl (Ref a -> Ref b -> IO ())) => Op (InsertWithBefore ()) Table orig impl 
(Parent a Widget, (~) * impl (Ref a -> Ref b -> IO ())) => Op (InsertWithBefore ()) Group orig impl 
(~) * impl (IO (Maybe (Ref Widget))) => Op (DdfdesignKludge ()) Group orig impl 
(Parent a Widget, (~) * impl (Ref a -> IO ())) => Op (Focus ()) Group orig impl 
(~) * impl (IO Int) => Op (ClipChildren ()) Group orig impl 
(~) * impl (Int -> IO ()) => Op (SetClipChildren ()) Group orig impl 
(~) * impl (IO Int) => Op (Children ()) TreeItem orig impl 
(~) * impl (IO Int) => Op (Children ()) Table orig impl 
(~) * impl (IO Int) => Op (Children ()) Group orig impl 
(~) * impl (IO ()) => Op (InitSizes ()) Table orig impl 
(~) * impl (IO ()) => Op (InitSizes ()) Group orig impl 
(Parent a Widget, (~) * impl (Ref a -> IO ())) => Op (AddResizable ()) Group orig impl 
(~) * impl (IO (Maybe (Ref Widget))) => Op (GetResizable ()) Group orig impl 
(~) * impl (IO ()) => Op (SetNotResizable ()) Group orig impl 
(Parent a Widget, (~) * impl (Maybe (Ref a) -> IO ())) => Op (SetResizable ()) Group orig impl 
(~) * impl (IO ()) => Op (Clear ()) Scrolled orig impl 
(~) * impl (IO ()) => Op (Clear ()) Tree orig impl 
(~) * impl (IO ()) => Op (Clear ()) Browser orig impl 
(~) * impl (IO ()) => Op (Clear ()) TableRow orig impl 
(~) * impl (IO ()) => Op (Clear ()) Table orig impl 
(~) * impl (IO ()) => Op (Clear ()) SysMenuBar orig impl 
(~) * impl (IO ()) => Op (Clear ()) MenuPrim orig impl 
(~) * impl (IO ()) => Op (Clear ()) MenuItem orig impl 
(~) * impl (IO Bool) => Op (Clear ()) Button orig impl 
(~) * impl (IO ()) => Op (Clear ()) Group orig impl 
(Parent a Widget, (~) * impl (Ref a -> IO ())) => Op (RemoveWidget ()) Group orig impl 
(~) * impl (Int -> IO ()) => Op (RemoveIndex ()) Group orig impl 
(~) * impl (BufferOffset -> String -> IO ()) => Op (Insert ()) TextBuffer orig impl 
(Parent a TreeItem, (~) * impl (Ref a -> String -> Int -> IO (Maybe (Ref a)))) => Op (Insert ()) Tree orig impl 
(Parent a TreePrefs, (~) * impl (Ref a -> String -> Maybe Int -> IO (Maybe (Ref TreeItem)))) => Op (Insert ()) TreeItem orig impl 
(~) * impl (Int -> String -> IO ()) => Op (Insert ()) Browser orig impl 
(Parent a Widget, (~) * impl (Ref a -> Int -> IO ())) => Op (Insert ()) Table orig impl 
(~) * impl (String -> IO (Either NoChange ())) => Op (Insert ()) Input orig impl 
(Parent a MenuPrim, (~) * impl (Int -> String -> Maybe Shortcut -> (Ref a -> IO ()) -> MenuItemFlags -> IO MenuItemIndex)) => Op (Insert ()) MenuPrim orig impl 
(Parent a MenuItem, (~) * impl (Int -> String -> Maybe ShortcutKeySequence -> (Ref a -> IO ()) -> MenuItemFlags -> IO MenuItemIndex)) => Op (Insert ()) MenuItem orig impl 
(Parent a Widget, (~) * impl (Ref a -> Int -> IO ())) => Op (Insert ()) Group orig impl 
(~) * impl (String -> IO (Maybe (Ref TreeItem))) => Op (Add ()) Tree orig impl 
(Parent a TreeItem, Parent b TreePrefs, (~) * impl (Ref b -> TreeItemLocator -> IO (Maybe (Ref a)))) => Op (Add ()) TreeItem orig impl 
(~) * impl (String -> IO ()) => Op (Add ()) Browser orig impl 
(Parent a Widget, (~) * impl (Ref a -> IO ())) => Op (Add ()) Table orig impl 
(Parent a MenuItem, (~) * impl (String -> Maybe Shortcut -> Maybe (Ref a -> IO ()) -> MenuItemFlags -> IO MenuItemIndex)) => Op (Add ()) MenuPrim orig impl 
(Parent a MenuItem, (~) * impl (String -> Maybe Shortcut -> Maybe (Ref a -> IO ()) -> MenuItemFlags -> IO MenuItemIndex)) => Op (Add ()) MenuItem orig impl 
(Parent a Widget, (~) * impl (Ref a -> IO ())) => Op (Add ()) Group orig impl 
(Parent a Widget, (~) * impl (Ref a -> IO Int)) => Op (Find ()) Table orig impl 
(Parent a Widget, (~) * impl (Ref a -> IO Int)) => Op (Find ()) Group orig impl 
(~) * impl (IO BufferOffset) => Op (End ()) TextSelection orig impl 
(~) * impl (IO ()) => Op (End ()) Table orig impl 
(~) * impl (IO ()) => Op (End ()) Group orig impl 
(~) * impl (IO ()) => Op (Begin ()) Table orig impl 
(~) * impl (IO ()) => Op (Begin ()) Group orig impl 
(Parent a Widget, (~) * impl (Ref a -> IO ())) => Op (UpdateChild ()) Group orig impl 
(Parent a Widget, (~) * impl (Ref a -> IO ())) => Op (DrawOutsideLabel ()) Group orig impl 
(~) * impl (IO ()) => Op (DrawChildren ()) Group orig impl 
(Parent a Widget, (~) * impl (Ref a -> IO ())) => Op (DrawChild ()) Group orig impl 
(~) * impl (Maybe (Boxtype, Rectangle) -> IO ()) => Op (DrawFocus ()) Button orig impl 
(~) * impl (Maybe (Boxtype, Rectangle) -> IO ()) => Op (DrawFocus ()) Window orig impl 
(~) * impl (Maybe (Boxtype, Rectangle) -> IO ()) => Op (DrawFocus ()) Widget orig impl 
(~) * impl (IO ()) => Op (DrawBackdrop ()) Button orig impl 
(~) * impl (IO ()) => Op (DrawBackdrop ()) Window orig impl 
(~) * impl (IO ()) => Op (DrawBackdrop ()) Widget orig impl 
(~) * impl (Boxtype -> Color -> Maybe Rectangle -> IO ()) => Op (DrawBoxWithBoxtype ()) Button orig impl 
(~) * impl (Boxtype -> Color -> Maybe Rectangle -> IO ()) => Op (DrawBoxWithBoxtype ()) Window orig impl 
(~) * impl (Boxtype -> Color -> Maybe Rectangle -> IO ()) => Op (DrawBoxWithBoxtype ()) Widget orig impl 
(~) * impl (IO ()) => Op (DrawBox ()) Button orig impl 
(~) * impl (IO ()) => Op (DrawBox ()) Window orig impl 
(~) * impl (IO ()) => Op (DrawBox ()) Widget orig impl 
(~) * impl (IO Bool) => Op (HasCallback ()) Widget orig impl 
(~) * impl ((Ref orig -> IO ()) -> IO ()) => Op (SetCallback ()) MenuItem orig impl 
(~) * impl ((Ref orig -> IO ()) -> IO ()) => Op (SetCallback ()) Window orig impl 
(~) * impl ((Ref orig -> IO ()) -> IO ()) => Op (SetCallback ()) Widget orig impl 
(~) * impl (Rectangle -> IO ()) => Op (Resize ()) Scrolled orig impl 
(~) * impl (Rectangle -> IO ()) => Op (Resize ()) Tile orig impl 
(~) * impl (Rectangle -> IO ()) => Op (Resize ()) TextDisplay orig impl 
(~) * impl (Rectangle -> IO ()) => Op (Resize ()) GlWindow orig impl 
(~) * impl (Rectangle -> IO ()) => Op (Resize ()) TableRow orig impl 
(~) * impl (Rectangle -> IO ()) => Op (Resize ()) Table orig impl 
(~) * impl (Rectangle -> IO ()) => Op (Resize ()) ValueOutput orig impl 
(~) * impl (Rectangle -> IO ()) => Op (Resize ()) ValueInput orig impl 
(~) * impl (Rectangle -> IO ()) => Op (Resize ()) MenuPrim orig impl 
(~) * impl (Rectangle -> IO ()) => Op (Resize ()) Valuator orig impl 
(~) * impl (Rectangle -> IO ()) => Op (Resize ()) Button orig impl 
(~) * impl (Rectangle -> IO ()) => Op (Resize ()) OverlayWindow orig impl 
(~) * impl (Rectangle -> IO ()) => Op (Resize ()) DoubleWindow orig impl 
(~) * impl (Rectangle -> IO ()) => Op (Resize ()) SingleWindow orig impl 
(~) * impl (Rectangle -> IO ()) => Op (Resize ()) Window orig impl 
(~) * impl (Rectangle -> IO ()) => Op (Resize ()) Widget orig impl 
(~) * impl (Rectangle -> IO ()) => Op (ResizeSuper ()) GlWindow orig impl 
(~) * impl (Rectangle -> IO ()) => Op (ResizeSuper ()) TableRow orig impl 
(~) * impl (Rectangle -> IO ()) => Op (ResizeSuper ()) Table orig impl 
(~) * impl (Rectangle -> IO ()) => Op (ResizeSuper ()) MenuPrim orig impl 
(~) * impl (Rectangle -> IO ()) => Op (ResizeSuper ()) Valuator orig impl 
(~) * impl (Rectangle -> IO ()) => Op (ResizeSuper ()) Button orig impl 
(~) * impl (Rectangle -> IO ()) => Op (ResizeSuper ()) DoubleWindow orig impl 
(~) * impl (Rectangle -> IO ()) => Op (ResizeSuper ()) SingleWindow orig impl 
(~) * impl (Rectangle -> IO ()) => Op (ResizeSuper ()) Window orig impl 
(~) * impl (Rectangle -> IO ()) => Op (ResizeSuper ()) Widget orig impl 
(~) * impl (IO Position) => Op (GetTopWindowOffset ()) Widget orig impl 
(~) * impl (IO (Maybe (Ref Window))) => Op (GetTopWindow ()) Widget orig impl 
(~) * impl (IO (Maybe (Ref Window))) => Op (GetWindow ()) Widget orig impl 
(~) * impl (IO Size) => Op (MeasureLabel ()) Widget orig impl 
(~) * impl (Word8 -> Rectangle -> IO ()) => Op (GetDamageInsideWidget ()) Widget orig impl 
(~) * impl (Word8 -> IO ()) => Op (GetDamageWithText ()) Widget orig impl 
(~) * impl (IO ()) => Op (ClearDamage ()) Widget orig impl 
(~) * impl (Word8 -> IO ()) => Op (ClearDamageWithBitmask ()) Widget orig impl 
(~) * impl (IO Word8) => Op (GetDamage ()) Widget orig impl 
(~) * impl (IO ()) => Op (RedrawLabel ()) Widget orig impl 
(~) * impl (IO ()) => Op (Redraw ()) Widget orig impl 
(Parent a Widget, (~) * impl (Ref a -> IO Int)) => Op (Inside ()) Widget orig impl 
(Parent a Widget, (~) * impl (Ref a -> IO Int)) => Op (Contains ()) Widget orig impl 
(~) * impl (IO Bool) => Op (GetVisibleFocus ()) Widget orig impl 
(~) * impl (Int -> IO ()) => Op (ModifyVisibleFocus ()) Widget orig impl 
(~) * impl (IO ()) => Op (ClearVisibleFocus ()) Widget orig impl 
(~) * impl (IO ()) => Op (SetVisibleFocus ()) Widget orig impl 
(~) * impl (IO (Either NoChange ())) => Op (TakeFocus ()) Widget orig impl 
(~) * impl (IO ()) => Op (ClearActive ()) Widget orig impl 
(~) * impl (IO ()) => Op (SetActive ()) Widget orig impl 
(~) * impl (IO ()) => Op (ClearChanged ()) Widget orig impl 
(~) * impl (IO ()) => Op (SetChanged ()) Widget orig impl 
(~) * impl (IO Bool) => Op (Takesevents ()) Widget orig impl 
(~) * impl (IO ()) => Op (ClearOutput ()) Widget orig impl 
(~) * impl (IO ()) => Op (SetOutput ()) Widget orig impl 
(~) * impl (IO Int) => Op (GetOutput ()) Widget orig impl 
(~) * impl (IO ()) => Op (Deactivate ()) MenuItem orig impl 
(~) * impl (IO ()) => Op (Deactivate ()) RepeatButton orig impl 
(~) * impl (IO ()) => Op (Deactivate ()) Widget orig impl 
(~) * impl (IO ()) => Op (Activate ()) TreeItem orig impl 
(~) * impl (IO ()) => Op (Activate ()) MenuItem orig impl 
(~) * impl (IO ()) => Op (Activate ()) Widget orig impl 
(~) * impl (IO Bool) => Op (ActiveR ()) Widget orig impl 
(~) * impl (IO Bool) => Op (Active ()) MenuItem orig impl 
(~) * impl (IO Bool) => Op (Active ()) Widget orig impl 
(~) * impl (IO ()) => Op (ClearVisible ()) Widget orig impl 
(~) * impl (IO ()) => Op (SetVisible ()) Widget orig impl 
(~) * impl (IO ()) => Op (Hide ()) Browser orig impl 
(~) * impl (IO ()) => Op (Hide ()) GlWindow orig impl 
(~) * impl (IO ()) => Op (Hide ()) Table orig impl 
(~) * impl (IO ()) => Op (Hide ()) MenuPrim orig impl 
(~) * impl (IO ()) => Op (Hide ()) MenuItem orig impl 
(~) * impl (IO ()) => Op (Hide ()) Button orig impl 
(~) * impl (IO ()) => Op (Hide ()) OverlayWindow orig impl 
(~) * impl (IO ()) => Op (Hide ()) DoubleWindow orig impl 
(~) * impl (IO ()) => Op (Hide ()) SingleWindow orig impl 
(~) * impl (IO ()) => Op (Hide ()) Window orig impl 
(~) * impl (IO ()) => Op (Hide ()) Widget orig impl 
(~) * impl (IO ()) => Op (HideSuper ()) GlWindow orig impl 
(~) * impl (IO ()) => Op (HideSuper ()) Table orig impl 
(~) * impl (IO ()) => Op (HideSuper ()) MenuPrim orig impl 
(~) * impl (IO ()) => Op (HideSuper ()) Button orig impl 
(~) * impl (IO ()) => Op (HideSuper ()) DoubleWindow orig impl 
(~) * impl (IO ()) => Op (HideSuper ()) SingleWindow orig impl 
(~) * impl (IO ()) => Op (HideSuper ()) Window orig impl 
(~) * impl (IO ()) => Op (HideSuper ()) Widget orig impl 
(~) * impl (IO NativeFileChooserUserAction) => Op (ShowWidget ()) NativeFileChooser orig impl 
(~) * impl (IO ()) => Op (ShowWidget ()) Browser orig impl 
(~) * impl (IO ()) => Op (ShowWidget ()) GlWindow orig impl 
(~) * impl (IO ()) => Op (ShowWidget ()) Table orig impl 
(~) * impl (IO ()) => Op (ShowWidget ()) MenuPrim orig impl 
(~) * impl (IO ()) => Op (ShowWidget ()) MenuItem orig impl 
(~) * impl (IO ()) => Op (ShowWidget ()) Button orig impl 
(~) * impl (IO ()) => Op (ShowWidget ()) OverlayWindow orig impl 
(~) * impl (IO ()) => Op (ShowWidget ()) DoubleWindow orig impl 
(~) * impl (IO ()) => Op (ShowWidget ()) SingleWindow orig impl 
(~) * impl (IO ()) => Op (ShowWidget ()) Window orig impl 
(~) * impl (IO ()) => Op (ShowWidget ()) Widget orig impl 
(~) * impl (IO ()) => Op (ShowWidgetSuper ()) GlWindow orig impl 
(~) * impl (IO ()) => Op (ShowWidgetSuper ()) Table orig impl 
(~) * impl (IO ()) => Op (ShowWidgetSuper ()) MenuPrim orig impl 
(~) * impl (IO ()) => Op (ShowWidgetSuper ()) Button orig impl 
(~) * impl (IO ()) => Op (ShowWidgetSuper ()) DoubleWindow orig impl 
(~) * impl (IO ()) => Op (ShowWidgetSuper ()) SingleWindow orig impl 
(~) * impl (IO ()) => Op (ShowWidgetSuper ()) Window orig impl 
(~) * impl (IO ()) => Op (ShowWidgetSuper ()) Widget orig impl 
(~) * impl (IO Bool) => Op (GetVisibleR ()) Widget orig impl 
(~) * impl (IO Bool) => Op (GetVisible ()) Widget orig impl 
(~) * impl ([When] -> IO ()) => Op (SetWhen ()) Widget orig impl 
(~) * impl (IO [When]) => Op (GetWhen ()) Widget orig impl 
(~) * impl (String -> IO ()) => Op (SetTooltip ()) Widget orig impl 
(~) * impl (String -> IO ()) => Op (CopyTooltip ()) Widget orig impl 
(~) * impl (IO String) => Op (GetTooltip ()) Widget orig impl 
(Parent a Image, (~) * impl (Maybe (Ref a) -> IO ())) => Op (SetDeimage ()) Widget orig impl 
(~) * impl (IO (Ref Image)) => Op (GetDeimage ()) Widget orig impl 
(Parent a Image, (~) * impl (Maybe (Ref a) -> IO ())) => Op (SetImage ()) Widget orig impl 
(~) * impl (IO (Ref Image)) => Op (GetImage ()) Widget orig impl 
(~) * impl (FontSize -> IO ()) => Op (SetLabelsize ()) TreeItem orig impl 
(~) * impl (FontSize -> IO ()) => Op (SetLabelsize ()) TreePrefs orig impl 
(~) * impl (FontSize -> IO ()) => Op (SetLabelsize ()) MenuItem orig impl 
(~) * impl (FontSize -> IO ()) => Op (SetLabelsize ()) Widget orig impl 
(~) * impl (IO FontSize) => Op (GetLabelsize ()) TreeItem orig impl 
(~) * impl (IO FontSize) => Op (GetLabelsize ()) TreePrefs orig impl 
(~) * impl (IO FontSize) => Op (GetLabelsize ()) MenuItem orig impl 
(~) * impl (IO FontSize) => Op (GetLabelsize ()) Widget orig impl 
(~) * impl (Font -> IO ()) => Op (SetLabelfont ()) TreeItem orig impl 
(~) * impl (Font -> IO ()) => Op (SetLabelfont ()) TreePrefs orig impl 
(~) * impl (Font -> IO ()) => Op (SetLabelfont ()) MenuItem orig impl 
(~) * impl (Font -> IO ()) => Op (SetLabelfont ()) Widget orig impl 
(~) * impl (IO Font) => Op (GetLabelfont ()) TreeItem orig impl 
(~) * impl (IO Font) => Op (GetLabelfont ()) TreePrefs orig impl 
(~) * impl (IO Font) => Op (GetLabelfont ()) MenuItem orig impl 
(~) * impl (IO Font) => Op (GetLabelfont ()) Widget orig impl 
(~) * impl (Color -> IO ()) => Op (SetLabelcolor ()) TreeItem orig impl 
(~) * impl (Color -> IO ()) => Op (SetLabelcolor ()) MenuItem orig impl 
(~) * impl (Color -> IO ()) => Op (SetLabelcolor ()) Widget orig impl 
(~) * impl (IO Color) => Op (GetLabelcolor ()) TreeItem orig impl 
(~) * impl (IO Color) => Op (GetLabelcolor ()) MenuItem orig impl 
(~) * impl (IO Color) => Op (GetLabelcolor ()) Widget orig impl 
(~) * impl (Labeltype -> IO ()) => Op (SetLabeltype ()) MenuItem orig impl 
(~) * impl (Labeltype -> IO ()) => Op (SetLabeltype ()) Widget orig impl 
(~) * impl (IO Labeltype) => Op (GetLabeltype ()) MenuItem orig impl 
(~) * impl (IO Labeltype) => Op (GetLabeltype ()) Widget orig impl 
(~) * impl (String -> IO ()) => Op (SetLabel ()) TreeItem orig impl 
(~) * impl (String -> IO ()) => Op (SetLabel ()) MenuItem orig impl 
(~) * impl (String -> IO ()) => Op (SetLabel ()) Window orig impl 
(~) * impl (String -> IO ()) => Op (SetLabel ()) Widget orig impl 
(~) * impl (String -> IO ()) => Op (CopyLabel ()) Window orig impl 
(~) * impl (String -> IO ()) => Op (CopyLabel ()) Widget orig impl 
(~) * impl (IO String) => Op (GetLabel ()) TreeItem orig impl 
(~) * impl (IO String) => Op (GetLabel ()) MenuItem orig impl 
(~) * impl (IO String) => Op (GetLabel ()) Window orig impl 
(~) * impl (IO String) => Op (GetLabel ()) Widget orig impl 
(~) * impl (Color -> IO ()) => Op (SetSelectionColor ()) Widget orig impl 
(~) * impl (IO Color) => Op (GetSelectionColor ()) Widget orig impl 
(~) * impl (Color -> Color -> IO ()) => Op (SetColorWithBgSel ()) Widget orig impl 
(~) * impl (Color -> IO ()) => Op (SetColor ()) Widget orig impl 
(~) * impl (IO Color) => Op (GetColor ()) Widget orig impl 
(~) * impl (Boxtype -> IO ()) => Op (SetBox ()) Widget orig impl 
(~) * impl (IO Boxtype) => Op (GetBox ()) Widget orig impl 
(~) * impl (IO Alignments) => Op (GetAlign ()) Widget orig impl 
(~) * impl (Alignments -> IO ()) => Op (SetAlign ()) Widget orig impl 
((~) * (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 Int), Op (GetY ()) obj orig (IO Int), Op (GetW ()) obj orig (IO Int), Op (GetH ()) obj orig (IO Int), (~) * impl (IO Rectangle)) => Op (GetRectangle ()) Widget orig impl 
(~) * impl (IO Int) => Op (GetH ()) RGBImage orig impl 
(~) * impl (IO Int) => Op (GetH ()) TreeItem orig impl 
(~) * impl (IO Int) => Op (GetH ()) Pixmap orig impl 
(~) * impl (IO Int) => Op (GetH ()) Bitmap orig impl 
(~) * impl (IO Int) => Op (GetH ()) Image orig impl 
(~) * impl (IO Int) => Op (GetH ()) Widget orig impl 
(~) * impl (IO Int) => Op (GetW ()) RGBImage orig impl 
(~) * impl (IO Int) => Op (GetW ()) TreeItem orig impl 
(~) * impl (IO Int) => Op (GetW ()) Pixmap orig impl 
(~) * impl (IO Int) => Op (GetW ()) Bitmap orig impl 
(~) * impl (IO Int) => Op (GetW ()) Image orig impl 
(~) * impl (IO Int) => Op (GetW ()) Widget orig impl 
(~) * impl (IO Int) => Op (GetY ()) TreeItem orig impl 
(~) * impl (IO Int) => Op (GetY ()) Widget orig impl 
(~) * impl (IO Int) => Op (GetX ()) TreeItem orig impl 
(~) * impl (IO Int) => Op (GetX ()) Widget orig impl 
(~) * impl (Maybe (Rectangle, Alignments) -> IO ()) => Op (DrawLabel ()) Widget orig impl 
(~) * impl (SpinnerType -> IO ()) => Op (SetType ()) Spinner orig impl 
(~) * impl (ScrollbarMode -> IO ()) => Op (SetType ()) Scrolled orig impl 
(~) * impl (PackType -> IO ()) => Op (SetType ()) Pack orig impl 
(~) * impl (NativeFileChooserType -> IO ()) => Op (SetType ()) NativeFileChooser orig impl 
(~) * impl (BrowserType -> IO ()) => Op (SetType ()) Browser orig impl 
(~) * impl (TableRowSelectMode -> IO ()) => Op (SetType ()) TableRow orig impl 
(~) * impl (FlOutputType -> IO ()) => Op (SetType ()) Output orig impl 
(~) * impl (FlInputType -> IO ()) => Op (SetType ()) Input orig impl 
(~) * impl (ScrollbarType -> IO ()) => Op (SetType ()) Scrollbar orig impl 
(~) * impl (CounterType -> IO ()) => Op (SetType ()) Counter orig impl 
(~) * impl (DialType -> IO ()) => Op (SetType ()) Dial orig impl 
(~) * impl (SliderType -> IO ()) => Op (SetType ()) Slider orig impl 
(~) * impl (ValuatorType -> IO ()) => Op (SetType ()) Valuator orig impl 
(~) * impl (ButtonType -> IO ()) => Op (SetType ()) Button orig impl 
(~) * impl (WindowType -> IO ()) => Op (SetType ()) Window orig impl 
(~) * impl (Word8 -> IO ()) => Op (SetType ()) Widget orig impl 
(~) * impl (IO SpinnerType) => Op (GetType_ ()) Spinner orig impl 
(~) * impl (IO ScrollbarMode) => Op (GetType_ ()) Scrolled orig impl 
(~) * impl (IO PackType) => Op (GetType_ ()) Pack orig impl 
(~) * impl (IO NativeFileChooserType) => Op (GetType_ ()) NativeFileChooser orig impl 
(~) * impl (IO BrowserType) => Op (GetType_ ()) Browser orig impl 
(~) * impl (IO TableRowSelectMode) => Op (GetType_ ()) TableRow orig impl 
(~) * impl (IO ScrollbarType) => Op (GetType_ ()) Scrollbar orig impl 
(~) * impl (IO CounterType) => Op (GetType_ ()) Counter orig impl 
(~) * impl (IO DialType) => Op (GetType_ ()) Dial orig impl 
(~) * impl (IO SliderType) => Op (GetType_ ()) Slider orig impl 
(~) * impl (IO ValuatorType) => Op (GetType_ ()) Valuator orig impl 
(~) * impl (IO ButtonType) => Op (GetType_ ()) Button orig impl 
(~) * impl (IO WindowType) => Op (GetType_ ()) Window orig impl 
(~) * impl (IO Word8) => Op (GetType_ ()) Widget orig impl 
(Parent a TreeItem, (~) * impl (Maybe (Ref a) -> IO ())) => Op (SetParent ()) TreeItem orig impl 
(Parent a Group, (~) * impl (Maybe (Ref a) -> IO ())) => Op (SetParent ()) Widget orig impl 
(~) * impl (IO (Maybe (Ref TreeItem))) => Op (GetParent ()) TreeItem orig impl 
(~) * impl (IO (Maybe (Ref Group))) => Op (GetParent ()) Widget orig impl 
(~) * impl (Event -> IO Int) => Op (Handle ()) Spinner orig impl 
(~) * impl (Event -> IO Int) => Op (Handle ()) Tabs orig impl 
(~) * impl (Int -> IO Int) => Op (Handle ()) Scrolled orig impl 
(~) * impl (Event -> IO Int) => Op (Handle ()) Tile orig impl 
(~) * impl (Event -> IO Int) => Op (Handle ()) TextEditor orig impl 
(~) * impl (Event -> IO Int) => Op (Handle ()) TextDisplay orig impl 
(~) * impl (Event -> IO Int) => Op (Handle ()) Tree orig impl 
(~) * impl (Event -> IO Int) => Op (Handle ()) Clock orig impl 
(~) * impl (Event -> IO Int) => Op (Handle ()) Browser orig impl 
(~) * impl (Event -> IO Int) => Op (Handle ()) Box orig impl 
(~) * impl (Event -> IO Int) => Op (Handle ()) GlWindow orig impl 
(~) * impl (Event -> IO Int) => Op (Handle ()) TableRow orig impl 
(~) * impl (Event -> IO Int) => Op (Handle ()) Table orig impl 
(~) * impl (Event -> IO Int) => Op (Handle ()) Positioner orig impl 
(~) * impl (Event -> IO Int) => Op (Handle ()) Timer orig impl 
(~) * impl (Event -> IO Int) => Op (Handle ()) ValueOutput orig impl 
(~) * impl (Event -> IO Int) => Op (Handle ()) ValueInput orig impl 
(~) * impl (Event -> IO Int) => Op (Handle ()) Input orig impl 
(~) * impl (Event -> IO Int) => Op (Handle ()) ValueSlider orig impl 
(~) * impl (Event -> IO Int) => Op (Handle ()) Scrollbar orig impl 
(~) * impl (Event -> IO Int) => Op (Handle ()) Counter orig impl 
(~) * impl (Event -> IO Int) => Op (Handle ()) Roller orig impl 
(~) * impl (Event -> IO Int) => Op (Handle ()) Dial orig impl 
(~) * impl (Event -> IO Int) => Op (Handle ()) MenuButton orig impl 
(~) * impl (Event -> IO Int) => Op (Handle ()) Choice orig impl 
(~) * impl (Event -> IO Int) => Op (Handle ()) SysMenuBar orig impl 
(~) * impl (Event -> IO Int) => Op (Handle ()) MenuPrim orig impl 
(~) * impl (Event -> IO Int) => Op (Handle ()) Slider orig impl 
(~) * impl (Event -> IO Int) => Op (Handle ()) Valuator orig impl 
(~) * impl (Event -> IO Int) => Op (Handle ()) RepeatButton orig impl 
(~) * impl (Event -> IO Int) => Op (Handle ()) ReturnButton orig impl 
(~) * impl (Event -> IO Int) => Op (Handle ()) Button orig impl 
(~) * impl (Event -> IO Int) => Op (Handle ()) DoubleWindow orig impl 
(~) * impl (Event -> IO Int) => Op (Handle ()) SingleWindow orig impl 
(~) * impl (Event -> IO Int) => Op (Handle ()) Window orig impl 
(~) * impl (Event -> IO Int) => Op (Handle ()) Widget orig impl 
(~) * impl (IO ()) => Op (Destroy ()) RGBImage orig impl 
(~) * impl (IO ()) => Op (Destroy ()) NativeFileChooser orig impl 
(~) * impl (IO ()) => Op (Destroy ()) TextEditor orig impl 
(~) * impl (IO ()) => Op (Destroy ()) TextDisplay orig impl 
(~) * impl (IO ()) => Op (Destroy ()) TextBuffer orig impl 
(~) * impl (IO ()) => Op (Destroy ()) Tree orig impl 
(~) * impl (IO ()) => Op (Destroy ()) TreeItem orig impl 
(~) * impl (IO ()) => Op (Destroy ()) Browser orig impl 
(~) * impl (IO ()) => Op (Destroy ()) GlWindow orig impl 
(~) * impl (IO ()) => Op (Destroy ()) TableRow orig impl 
(~) * impl (IO ()) => Op (Destroy ()) Table orig impl 
(~) * impl (IO ()) => Op (Destroy ()) Wizard orig impl 
(~) * impl (IO ()) => Op (Destroy ()) Positioner orig impl 
(~) * impl (IO ()) => Op (Destroy ()) Progress orig impl 
(~) * impl (IO ()) => Op (Destroy ()) Timer orig impl 
(~) * impl (IO ()) => Op (Destroy ()) ValueOutput orig impl 
(~) * impl (IO ()) => Op (Destroy ()) ValueInput orig impl 
(~) * impl (IO ()) => Op (Destroy ()) Input orig impl 
(~) * impl (IO ()) => Op (Destroy ()) ValueSlider orig impl 
(~) * impl (IO ()) => Op (Destroy ()) Scrollbar orig impl 
(~) * impl (IO ()) => Op (Destroy ()) Counter orig impl 
(~) * impl (IO ()) => Op (Destroy ()) Roller orig impl 
(~) * impl (IO ()) => Op (Destroy ()) Dial orig impl 
(~) * impl (IO ()) => Op (Destroy ()) Adjuster orig impl 
(~) * impl (IO ()) => Op (Destroy ()) ImageSurface orig impl 
(~) * impl (IO ()) => Op (Destroy ()) CopySurface orig impl 
(~) * impl (IO ()) => Op (Destroy ()) Pixmap orig impl 
(~) * impl (IO ()) => Op (Destroy ()) Bitmap orig impl 
(~) * impl (IO ()) => Op (Destroy ()) Image orig impl 
(~) * impl (IO ()) => Op (Destroy ()) MenuButton orig impl 
(~) * impl (IO ()) => Op (Destroy ()) Choice orig impl 
(~) * impl (IO ()) => Op (Destroy ()) SysMenuBar orig impl 
(~) * impl (IO ()) => Op (Destroy ()) MenuPrim orig impl 
(~) * impl (IO ()) => Op (Destroy ()) MenuItem orig impl 
(~) * impl (IO ()) => Op (Destroy ()) Slider orig impl 
(~) * impl (IO ()) => Op (Destroy ()) Valuator orig impl 
(~) * impl (IO ()) => Op (Destroy ()) ToggleButton orig impl 
(~) * impl (IO ()) => Op (Destroy ()) RepeatButton orig impl 
(~) * impl (IO ()) => Op (Destroy ()) RoundButton orig impl 
(~) * impl (IO ()) => Op (Destroy ()) ReturnButton orig impl 
(~) * impl (IO ()) => Op (Destroy ()) CheckButton orig impl 
(~) * impl (IO ()) => Op (Destroy ()) LightButton orig impl 
(~) * impl (IO ()) => Op (Destroy ()) Button orig impl 
(~) * impl (IO ()) => Op (Destroy ()) OverlayWindow orig impl 
(~) * impl (IO ()) => Op (Destroy ()) DoubleWindow orig impl 
(~) * impl (IO ()) => Op (Destroy ()) SingleWindow orig impl 
(~) * impl (IO ()) => Op (Destroy ()) Window orig impl 
(~) * impl (IO ()) => Op (Destroy ()) Group orig impl 
(~) * impl (IO ()) => Op (Destroy ()) Widget orig impl 

dispatch

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

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

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

runOp

castTo

castTo :: Ref a -> Ref r Source

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

safeCast

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

Cast any reference to one of its ancestors.

Parent

class Parent a b Source

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

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

Instances

(~) * InHierarchy (FindInHierarchy a a b) => Parent a b