fltkhs-0.8.0.2: FLTK bindings

Safe HaskellNone
LanguageHaskell2010

Graphics.UI.FLTK.LowLevel.Base.Browser

Contents

Synopsis

Constructor

Hierarchy

Functions

add :: Ref BrowserBase -> Text -> IO ()

clear :: Ref BrowserBase -> IO ()

deselect :: Ref BrowserBase -> IO (Either NoChange ())

deselectAndCallback :: Ref BrowserBase -> IO (Either NoChange ())

destroy :: Ref BrowserBase -> IO ()

displayed :: Ref BrowserBase -> LineNumber -> IO (Bool)

draw :: Ref BrowserBase -> IO ()

getColumnChar :: Ref BrowserBase -> IO (Char)

getColumnWidths :: Ref BrowserBase -> IO [Int]

getFormatChar :: Ref BrowserBase -> IO (Char)

getHasScrollbar :: Ref BrowserBase -> IO (ScrollbarMode)

getHposition :: Ref BrowserBase -> IO (PixelPosition)

getIcon :: Ref BrowserBase -> LineNumber -> IO (Maybe (Ref Image))

getPosition :: Ref BrowserBase -> IO (PixelPosition)

getScrollbarSize :: Ref BrowserBase -> IO (Int)

getScrollbarWidth :: Ref BrowserBase -> IO (Int)

getSize :: Ref BrowserBase -> IO (Int)

getText :: Ref BrowserBase -> LineNumber -> IO Text

getTextcolor :: Ref BrowserBase -> IO (Color)

getTextfont :: Ref BrowserBase -> IO (Font)

getTextsize :: Ref BrowserBase -> IO (FontSize)

getTopline :: Ref BrowserBase -> IO (LineNumber)

getType_ :: Ref BrowserBase -> IO (BrowserType)

getValue :: Ref BrowserBase -> IO (LineNumber)

handle :: Ref BrowserBase -> Event -> IO (Either UnknownEvent ())

hide :: Ref BrowserBase -> IO ()

hideLine :: Ref BrowserBase -> LineNumber -> IO ()

insert :: Ref BrowserBase -> LineNumber -> Text -> IO ()

lineposition :: Ref BrowserBase -> LineNumber -> LinePosition -> IO ()

load :: Ref BrowserBase -> Text -> IO (Either UnknownError ())

makeVisible :: Ref BrowserBase -> LineNumber -> IO ()

move :: Ref BrowserBase -> LineNumber -> LineNumber -> IO ()

remove :: Ref BrowserBase -> LineNumber -> IO ()

removeIcon :: Ref BrowserBase -> LineNumber -> IO ()

resize :: Ref BrowserBase -> Rectangle -> IO ()

select :: Ref BrowserBase -> LineNumber -> Bool -> IO (Either NoChange ())

selected :: Ref BrowserBase -> LineNumber -> IO (Bool)

setBottomline :: Ref BrowserBase -> LineNumber -> IO ()

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

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

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

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

setHposition :: Ref BrowserBase -> PixelPosition -> IO ()

setIcon :: Ref BrowserBase -> LineNumber -> Ref Image -> IO ()

setMiddleline :: Ref BrowserBase -> LineNumber -> IO ()

setPosition :: Ref BrowserBase -> PixelPosition -> IO ()

setScrollbarColor :: Ref BrowserBase -> Color -> IO ()

setScrollbarSelectionColor :: Ref BrowserBase -> Color -> IO ()

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

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

setSize :: Ref BrowserBase -> Size -> IO ()

setText :: Ref BrowserBase -> LineNumber -> Text -> IO ()

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

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

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

setTopline :: Ref BrowserBase -> LineNumber -> IO ()

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

setValue :: Ref BrowserBase -> LineNumber -> IO ()

showWidget :: Ref BrowserBase -> IO ()

showWidgetLine :: Ref BrowserBase -> LineNumber -> IO ()

sort :: Ref BrowserBase -> IO ()

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

swap :: Ref BrowserBase -> LineNumber -> LineNumber -> IO ()

visible :: Ref BrowserBase -> LineNumber -> IO (Bool)

Orphan instances

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

impl ~ IO Int => Op (GetScrollbarSize ()) BrowserBase orig impl Source # 
Instance details

Methods

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

impl ~ (ScrollbarMode -> IO ()) => Op (SetHasScrollbar ()) BrowserBase orig impl Source # 
Instance details

Methods

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

impl ~ IO ScrollbarMode => Op (GetHasScrollbar ()) BrowserBase orig impl Source # 
Instance details

Methods

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

impl ~ (PixelPosition -> IO ()) => Op (SetHposition ()) BrowserBase orig impl Source # 
Instance details

Methods

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

impl ~ IO PixelPosition => Op (GetHposition ()) BrowserBase orig impl Source # 
Instance details

Methods

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

impl ~ IO (Either NoChange ()) => Op (DeselectAndCallback ()) BrowserBase orig impl Source # 
Instance details

Methods

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

impl ~ IO (Either NoChange ()) => Op (Deselect ()) BrowserBase orig impl Source # 
Instance details

Methods

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

impl ~ (LineNumber -> IO ()) => Op (RemoveIcon ()) BrowserBase orig impl Source # 
Instance details

Methods

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

impl ~ (LineNumber -> IO ()) => Op (MakeVisible ()) BrowserBase orig impl Source # 
Instance details

Methods

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

impl ~ (LineNumber -> IO Bool) => Op (Displayed ()) BrowserBase orig impl Source # 
Instance details

Methods

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

impl ~ ([Int] -> IO ()) => Op (SetColumnWidths ()) BrowserBase orig impl Source # 
Instance details

Methods

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

impl ~ IO [Int] => Op (GetColumnWidths ()) BrowserBase orig impl Source # 
Instance details

Methods

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

impl ~ (Char -> IO ()) => Op (SetColumnChar ()) BrowserBase orig impl Source # 
Instance details

Methods

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

impl ~ IO Char => Op (GetColumnChar ()) BrowserBase orig impl Source # 
Instance details

Methods

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

impl ~ (Char -> IO ()) => Op (SetFormatChar ()) BrowserBase orig impl Source # 
Instance details

Methods

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

impl ~ IO Char => Op (GetFormatChar ()) BrowserBase orig impl Source # 
Instance details

Methods

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

impl ~ (LineNumber -> Text -> IO ()) => Op (SetText ()) BrowserBase orig impl Source # 
Instance details

Methods

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

impl ~ (LineNumber -> IO ()) => Op (HideLine ()) BrowserBase orig impl Source # 
Instance details

Methods

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

impl ~ (LineNumber -> IO ()) => Op (ShowWidgetLine ()) BrowserBase orig impl Source # 
Instance details

Methods

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

impl ~ (LineNumber -> IO Bool) => Op (Selected ()) BrowserBase orig impl Source # 
Instance details

Methods

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

impl ~ (LineNumber -> Bool -> IO (Either NoChange ())) => Op (Select ()) BrowserBase orig impl Source # 
Instance details

Methods

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

impl ~ (LineNumber -> IO ()) => Op (SetMiddleline ()) BrowserBase orig impl Source # 
Instance details

Methods

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

impl ~ (LineNumber -> IO ()) => Op (SetBottomline ()) BrowserBase orig impl Source # 
Instance details

Methods

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

impl ~ (LineNumber -> IO ()) => Op (SetTopline ()) BrowserBase orig impl Source # 
Instance details

Methods

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

impl ~ (LineNumber -> LinePosition -> IO ()) => Op (Lineposition ()) BrowserBase orig impl Source # 
Instance details

Methods

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

impl ~ IO LineNumber => Op (GetTopline ()) BrowserBase orig impl Source # 
Instance details

Methods

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

impl ~ (LineNumber -> LineNumber -> IO ()) => Op (Swap ()) BrowserBase orig impl Source # 
Instance details

Methods

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

impl ~ (Text -> IO (Either UnknownError ())) => Op (Load ()) BrowserBase orig impl Source # 
Instance details

Methods

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

impl ~ (LineNumber -> LineNumber -> IO ()) => Op (Move ()) BrowserBase orig impl Source # 
Instance details

Methods

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

impl ~ (PixelPosition -> IO ()) => Op (SetPosition ()) BrowserBase orig impl Source # 
Instance details

Methods

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

impl ~ IO PixelPosition => Op (GetPosition ()) BrowserBase orig impl Source # 
Instance details

Methods

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

impl ~ (Color -> IO ()) => Op (SetTextcolor ()) BrowserBase orig impl Source # 
Instance details

Methods

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

impl ~ IO Color => Op (GetTextcolor ()) BrowserBase orig impl Source # 
Instance details

Methods

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

impl ~ (FontSize -> IO ()) => Op (SetTextsize ()) BrowserBase orig impl Source # 
Instance details

Methods

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

impl ~ IO FontSize => Op (GetTextsize ()) BrowserBase orig impl Source # 
Instance details

Methods

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

impl ~ (Font -> IO ()) => Op (SetTextfont ()) BrowserBase orig impl Source # 
Instance details

Methods

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

impl ~ IO Font => Op (GetTextfont ()) BrowserBase orig impl Source # 
Instance details

Methods

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

impl ~ (LineNumber -> IO Text) => Op (GetText ()) BrowserBase orig impl Source # 
Instance details

Methods

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

impl ~ (LineNumber -> IO ()) => Op (Remove ()) BrowserBase orig impl Source # 
Instance details

Methods

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

impl ~ (Size -> IO ()) => Op (SetSize ()) BrowserBase orig impl Source # 
Instance details

Methods

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

impl ~ IO Int => Op (GetSize ()) BrowserBase orig impl Source # 
Instance details

Methods

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

impl ~ IO () => Op (Draw ()) BrowserBase orig impl Source # 
Instance details

Methods

runOp :: Draw () -> orig -> Ref BrowserBase -> impl Source #

impl ~ (LineNumber -> IO Bool) => Op (Visible ()) BrowserBase orig impl Source # 
Instance details

Methods

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

impl ~ (LineNumber -> IO ()) => Op (SetValue ()) BrowserBase orig impl Source # 
Instance details

Methods

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

impl ~ IO LineNumber => Op (GetValue ()) BrowserBase orig impl Source # 
Instance details

Methods

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

impl ~ (LineNumber -> Ref Image -> IO ()) => Op (SetIcon ()) BrowserBase orig impl Source # 
Instance details

Methods

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

impl ~ (LineNumber -> IO (Maybe (Ref Image))) => Op (GetIcon ()) BrowserBase orig impl Source # 
Instance details

Methods

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

impl ~ IO () => Op (Clear ()) BrowserBase orig impl Source # 
Instance details

Methods

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

impl ~ (LineNumber -> Text -> IO ()) => Op (Insert ()) BrowserBase orig impl Source # 
Instance details

Methods

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

impl ~ (Text -> IO ()) => Op (Add ()) BrowserBase orig impl Source # 
Instance details

Methods

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

impl ~ (Rectangle -> IO ()) => Op (Resize ()) BrowserBase orig impl Source # 
Instance details

Methods

runOp :: Resize () -> orig -> Ref BrowserBase -> impl Source #

impl ~ IO () => Op (Hide ()) BrowserBase orig impl Source # 
Instance details

Methods

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

impl ~ IO () => Op (ShowWidget ()) BrowserBase orig impl Source # 
Instance details

Methods

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

impl ~ (BrowserType -> IO ()) => Op (SetType ()) BrowserBase orig impl Source # 
Instance details

Methods

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

impl ~ IO BrowserType => Op (GetType_ ()) BrowserBase orig impl Source # 
Instance details

Methods

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

impl ~ (Event -> IO (Either UnknownEvent ())) => Op (Handle ()) BrowserBase orig impl Source # 
Instance details

Methods

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

impl ~ IO () => Op (Destroy ()) BrowserBase orig impl Source # 
Instance details

Methods

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