fltkhs-0.4.0.9: FLTK bindings

Safe HaskellNone
LanguageHaskell2010

Graphics.UI.FLTK.LowLevel.Browser

Contents

Synopsis

Constructor

Hierarchy

Functions

add :: Ref Browser -> String -> IO ()

clear :: Ref Browser -> IO ()

deselect :: Ref Browser -> IO (Int)

deselectAndCallback :: Ref Browser -> Int -> IO (Int)

destroy :: Ref Browser -> IO ()

displayed :: Ref Browser -> Int -> IO (Bool)

getColumnChar :: Ref Browser -> IO (Char)

getColumnWidths :: Ref Browser -> IO [Int]

getFormatChar :: Ref Browser -> IO (Char)

getHasScrollbar :: Ref Browser -> IO (ScrollbarMode)

getHposition :: Ref Browser -> IO (Int)

getIcon :: Ref Browser -> Int -> IO (Maybe (Ref Image))

getPosition :: Ref Browser -> IO (Int)

getScrollbarSize :: Ref Browser -> IO (Int)

getScrollbarWidth :: Ref Browser -> IO (Int)

getSize :: Ref Browser -> IO (Int)

getText :: Ref Browser -> Int -> IO (String)

getTextcolor :: Ref Browser -> IO (Color)

getTextfont :: Ref Browser -> IO (Font)

getTextsize :: Ref Browser -> IO (FontSize)

getTopline :: Ref Browser -> IO (Int)

getType_ :: Ref Browser -> IO (BrowserType)

getValue :: Ref Browser -> IO (Int)

handle :: Ref Browser -> Event -> IO Int

hide :: Ref Browser -> IO ()

hideLine :: Ref Browser -> Int -> IO ()

insert :: Ref Browser -> Int -> String -> IO ()

lineposition :: Ref Browser -> Int -> LinePosition -> IO ()

load :: Ref Browser -> String -> IO (Int)

makeVisible :: Ref Browser -> Int -> IO ()

move :: Ref Browser -> Int -> Int -> IO ()

remove :: Ref Browser -> Int -> IO ()

removeIcon :: Ref Browser -> Int -> IO ()

select :: Ref Browser -> Int -> Bool -> IO (Int)

selected :: Ref Browser -> Int -> IO (Bool)

setBottomline :: Ref Browser -> Int -> IO ()

setColumnChar :: Ref Browser -> Char -> IO ()

setColumnWidths :: Ref Browser -> [Int] -> IO ()

setFormatChar :: Ref Browser -> Char -> IO ()

setHasScrollbar :: Ref Browser -> ScrollbarMode>- IO ()

setHposition :: Ref Browser -> Int -> IO ()

setIcon :: Ref Browser -> Int -> Ref Image -> IO ()

setMiddleline :: Ref Browser -> Int -> IO ()

setPosition :: Ref Browser -> Int -> IO ()

setScrollbarSize :: Ref Browser -> Int -> IO ()

setScrollbarWidth :: Ref Browser -> Int -> IO ()

setSize :: Ref Browser -> Int -> Int -> IO ()

setText :: Ref Browser -> Int -> String -> IO ()

setTextcolor :: Ref Browser -> Color -> IO ()

setTextfont :: Ref Browser -> Font -> IO ()

setTextsize :: Ref Browser -> FontSize -> IO ()

setTopline :: Ref Browser -> Int -> IO ()

setType :: Ref Browser -> BrowserType -> IO ()

setValue :: Ref Browser -> Int -> IO ()

showWidget :: Ref Browser -> IO ()

showWidgetLine :: Ref Browser -> Int -> IO ()

sort :: Ref Browser -> IO ()

sortWithSortType :: Ref Browser -> SortType -> IO ()

swap :: Ref Browser -> Int -> Int -> IO ()

visible :: Ref Browser -> Int -> IO (Int)

Orphan instances

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

(~) * impl (Int -> IO ()) => Op (SetScrollbarSize ()) Browser orig impl Source # 

Methods

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

(~) * impl (IO Int) => Op (GetScrollbarSize ()) Browser orig impl Source # 

Methods

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

(~) * impl (ScrollbarMode -> IO ()) => Op (SetHasScrollbar ()) Browser orig impl Source # 

Methods

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

(~) * impl (IO ScrollbarMode) => Op (GetHasScrollbar ()) Browser orig impl Source # 

Methods

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

(~) * impl (Int -> IO ()) => Op (SetHposition ()) Browser orig impl Source # 

Methods

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

(~) * impl (IO Int) => Op (GetHposition ()) Browser orig impl Source # 

Methods

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

(~) * impl (Int -> IO Int) => Op (DeselectAndCallback ()) Browser orig impl Source # 

Methods

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

(~) * impl (IO Int) => Op (Deselect ()) Browser orig impl Source # 

Methods

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

(~) * impl (Int -> IO ()) => Op (RemoveIcon ()) Browser orig impl Source # 

Methods

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

(~) * impl (Int -> IO ()) => Op (MakeVisible ()) Browser orig impl Source # 

Methods

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

(~) * impl (Int -> IO Bool) => Op (Displayed ()) Browser orig impl Source # 

Methods

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

(~) * impl ([Int] -> IO ()) => Op (SetColumnWidths ()) Browser orig impl Source # 

Methods

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

(~) * impl (IO [Int]) => Op (GetColumnWidths ()) Browser orig impl Source # 

Methods

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

(~) * impl (Char -> IO ()) => Op (SetColumnChar ()) Browser orig impl Source # 

Methods

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

(~) * impl (IO Char) => Op (GetColumnChar ()) Browser orig impl Source # 

Methods

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

(~) * impl (Char -> IO ()) => Op (SetFormatChar ()) Browser orig impl Source # 

Methods

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

(~) * impl (IO Char) => Op (GetFormatChar ()) Browser orig impl Source # 

Methods

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

(~) * impl (Int -> String -> IO ()) => Op (SetText ()) Browser orig impl Source # 

Methods

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

(~) * impl (Int -> IO ()) => Op (HideLine ()) Browser orig impl Source # 

Methods

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

(~) * impl (Int -> IO ()) => Op (ShowWidgetLine ()) Browser orig impl Source # 

Methods

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

(~) * impl (Int -> IO Bool) => Op (Selected ()) Browser orig impl Source # 

Methods

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

(~) * impl (Int -> Bool -> IO Int) => Op (Select ()) Browser orig impl Source # 

Methods

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

(~) * impl (Int -> IO ()) => Op (SetMiddleline ()) Browser orig impl Source # 

Methods

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

(~) * impl (Int -> IO ()) => Op (SetBottomline ()) Browser orig impl Source # 

Methods

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

(~) * impl (Int -> IO ()) => Op (SetTopline ()) Browser orig impl Source # 

Methods

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

(~) * impl (Int -> LinePosition -> IO ()) => Op (Lineposition ()) Browser orig impl Source # 

Methods

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

(~) * impl (IO Int) => Op (GetTopline ()) Browser orig impl Source # 

Methods

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

(~) * impl (Int -> Int -> IO ()) => Op (Swap ()) Browser orig impl Source # 

Methods

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

(~) * impl (String -> IO Int) => Op (Load ()) Browser orig impl Source # 

Methods

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

(~) * impl (Int -> Int -> IO ()) => Op (Move ()) Browser orig impl Source # 

Methods

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

(~) * impl (Int -> IO ()) => Op (SetPosition ()) Browser orig impl Source # 

Methods

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

(~) * impl (IO Int) => Op (GetPosition ()) Browser orig impl Source # 

Methods

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

(~) * impl (Color -> IO ()) => Op (SetTextcolor ()) Browser orig impl Source # 

Methods

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

(~) * impl (IO Color) => Op (GetTextcolor ()) Browser orig impl Source # 

Methods

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

(~) * impl (FontSize -> IO ()) => Op (SetTextsize ()) Browser orig impl Source # 

Methods

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

(~) * impl (IO FontSize) => Op (GetTextsize ()) Browser orig impl Source # 

Methods

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

(~) * impl (Font -> IO ()) => Op (SetTextfont ()) Browser orig impl Source # 

Methods

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

(~) * impl (IO Font) => Op (GetTextfont ()) Browser orig impl Source # 

Methods

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

(~) * impl (Int -> IO String) => Op (GetText ()) Browser orig impl Source # 

Methods

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

(~) * impl (Int -> IO ()) => Op (Remove ()) Browser orig impl Source # 

Methods

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

(~) * impl (Int -> Int -> IO ()) => Op (SetSize ()) Browser orig impl Source # 

Methods

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

(~) * impl (IO Int) => Op (GetSize ()) Browser orig impl Source # 

Methods

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

(~) * impl (Int -> IO Int) => Op (Visible ()) Browser orig impl Source # 

Methods

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

(~) * impl (Int -> IO ()) => Op (SetValue ()) Browser orig impl Source # 

Methods

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

(~) * impl (IO Int) => Op (GetValue ()) Browser orig impl Source # 

Methods

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

(~) * impl (Int -> Ref Image -> IO ()) => Op (SetIcon ()) Browser orig impl Source # 

Methods

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

(~) * impl (Int -> IO (Maybe (Ref Image))) => Op (GetIcon ()) Browser orig impl Source # 

Methods

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

(~) * impl (IO ()) => Op (Clear ()) Browser orig impl Source # 

Methods

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

(~) * impl (Int -> String -> IO ()) => Op (Insert ()) Browser orig impl Source # 

Methods

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

(~) * impl (String -> IO ()) => Op (Add ()) Browser orig impl Source # 

Methods

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

(~) * impl (IO ()) => Op (Hide ()) Browser orig impl Source # 

Methods

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

(~) * impl (IO ()) => Op (ShowWidget ()) Browser orig impl Source # 

Methods

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

(~) * impl (BrowserType -> IO ()) => Op (SetType ()) Browser orig impl Source # 

Methods

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

(~) * impl (IO BrowserType) => Op (GetType_ ()) Browser orig impl Source # 

Methods

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

(~) * impl (Event -> IO Int) => Op (Handle ()) Browser orig impl Source # 

Methods

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

(~) * impl (IO ()) => Op (Destroy ()) Browser orig impl Source # 

Methods

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