fltkhs-0.7.0.0: FLTK bindings

Safe HaskellNone
LanguageHaskell2010

Graphics.UI.FLTK.LowLevel.Table

Contents

Synopsis

Documentation

data Row Source #

Constructors

Row Int 

data Column Source #

Constructors

Column Int 

data CustomTableFuncs a Source #

Constructors

CustomTableFuncs 

Fields

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

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

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

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

tableCustom Source #

Arguments

:: Rectangle

Bounds of this table

-> Maybe Text

Optional label

-> Maybe (Ref Table -> IO ())

Optional custom table drawing function

-> (Ref Table -> TableContext -> TableCoordinate -> Rectangle -> IO ())

Custom table cell drawing function

-> CustomWidgetFuncs Table

Widget overrides

-> CustomTableFuncs Table

Table overrides

-> IO (Ref Table) 

Hierarchy

Table functions

add:: (Parent a Widget) => Ref Table -> Ref a -> IO ()

begin :: Ref Table -> IO ()

callbackCol :: Ref Table -> IO (Column)

callbackContext :: Ref Table -> IO (TableContext)

callbackRow :: Ref Table -> IO (Row)

children :: Ref Table -> IO (Int)

clear :: Ref Table -> IO ()

clearSuper :: Ref Table -> IO ()

destroy :: Ref Table -> IO ()

doCallback :: Ref Table -> TableContext -> TableCoordinate -> IO ()

draw :: Ref Table -> IO ()

drawSuper :: Ref Table -> IO ()

end :: Ref Table -> IO ()

find:: (Parent a Widget) => Ref Table -> Ref a -> IO (Int)

findCell :: Ref Table -> TableContext -> TableCoordinate -> IO (Maybe Rectangle)

getArray :: Ref Table -> IO [Ref Widget]

getChild :: Ref Table -> AtIndex -> IO (Maybe (Ref Widget))

getColHeader :: Ref Table -> IO (Bool)

getColHeaderColor :: Ref Table -> IO (Color)

getColHeaderHeight :: Ref Table -> IO (Int)

getColPosition :: Ref Table -> IO (Column)

getColResize :: Ref Table -> IO (Bool)

getColResizeMin :: Ref Table -> IO (Int)

getColWidth :: Ref Table -> Column -> IO (Int)

getCols :: Ref Table -> IO (Columns)

getRowHeader :: Ref Table -> IO Bool

getRowHeaderColor :: Ref Table -> IO (Color)

getRowHeaderWidth :: Ref Table -> IO (Int)

getRowHeight :: Ref Table -> Row -> IO (Int)

getRowPosition :: Ref Table -> IO (Row)

getRowResize :: Ref Table -> IO (Bool)

getRowResizeMin :: Ref Table -> IO (Int)

getRows :: Ref Table -> IO (Rows)

getSelection :: Ref Table -> IO (TableCoordinate, TableCoordinate)

getTabCellNav :: Ref Table -> IO (Bool)

getTableBox :: Ref Table -> IO (Boxtype)

getTopRow :: Ref Table -> IO (Row)

getVisibleCells :: Ref Table -> IO ('TableCoordinate,TableCoordinate')

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

hide :: Ref Table -> IO ()

hideSuper :: Ref Table -> IO ()

initSizes :: Ref Table -> IO ()

insert:: (Parent a Widget) => Ref Table -> Ref a -> AtIndex -> IO ()

insertBefore:: (Parent a Widget, Parent b Widget) => Ref Table -> Ref a -> Ref b -> IO ()

isInteractiveResize :: Ref Table -> IO (Bool)

isSelected :: Ref Table -> TableCoordinate -> IO Bool

moveCursor :: Ref Table -> TableCoordinate -> IO (Either NoChange ())

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

resizeSuper :: Ref Table -> Rectangle -> IO ()

setColHeader :: Ref Table -> Bool -> IO ()

setColHeaderColor :: Ref Table -> Color -> IO ()

setColHeaderHeight :: Ref Table -> Int -> IO ()

setColPosition :: Ref Table -> Column -> IO ()

setColResize :: Ref Table -> Bool -> IO ()

setColResizeMin :: Ref Table -> Int -> IO ()

setColWidth :: Ref Table -> Column -> Int -> IO ()

setColWidthAll :: Ref Table -> Int -> IO ()

setCols :: Ref Table -> Columns -> IO ()

setColsSuper :: Ref Table -> Columns -> IO ()

setRowHeader :: Ref Table -> Bool -> IO ()

setRowHeaderColor :: Ref Table -> Color -> IO ()

setRowHeaderWidth :: Ref Table -> Int -> IO ()

setRowHeight :: Ref Table -> Row -> Int -> IO ()

setRowHeightAll :: Ref Table -> Int -> IO ()

setRowPosition :: Ref Table -> Row -> IO ()

setRowResize :: Ref Table -> Bool -> IO ()

setRowResizeMin :: Ref Table -> Int -> IO ()

setRows :: Ref Table -> Rows -> IO ()

setRowsSuper :: Ref Table -> Rows -> IO ()

setSelection :: Ref Table -> TableCoordinate -> TableCoordinate ->IO ()

setTabCellNav :: Ref Table -> Bool -> IO ()

setTableBox :: Ref Table -> Boxtype -> IO ()

setTopRow :: Ref Table -> Row -> IO ()

showWidget :: Ref Table -> IO ()

showWidgetSuper :: Ref Table -> IO ()

Orphan instances

impl ~ IO Bool => Op (GetTabCellNav ()) Table orig impl Source # 
Instance details

Methods

runOp :: GetTabCellNav () -> orig -> Ref Table -> impl Source #

impl ~ (Bool -> IO ()) => Op (SetTabCellNav ()) Table orig impl Source # 
Instance details

Methods

runOp :: SetTabCellNav () -> orig -> Ref Table -> impl Source #

impl ~ (Columns -> IO ()) => Op (SetColsSuper ()) Table orig impl Source # 
Instance details

Methods

runOp :: SetColsSuper () -> orig -> Ref Table -> impl Source #

impl ~ (Rows -> IO ()) => Op (SetRowsSuper ()) Table orig impl Source # 
Instance details

Methods

runOp :: SetRowsSuper () -> orig -> Ref Table -> impl Source #

impl ~ IO () => Op (ClearSuper ()) Table orig impl Source # 
Instance details

Methods

runOp :: ClearSuper () -> orig -> Ref Table -> impl Source #

impl ~ (TableContext -> TableCoordinate -> IO (Maybe Rectangle)) => Op (FindCell ()) Table orig impl Source # 
Instance details

Methods

runOp :: FindCell () -> orig -> Ref Table -> impl Source #

impl ~ IO TableContext => Op (CallbackContext ()) Table orig impl Source # 
Instance details

Methods

runOp :: CallbackContext () -> orig -> Ref Table -> impl Source #

impl ~ IO Column => Op (CallbackCol ()) Table orig impl Source # 
Instance details

Methods

runOp :: CallbackCol () -> orig -> Ref Table -> impl Source #

impl ~ IO Row => Op (CallbackRow ()) Table orig impl Source # 
Instance details

Methods

runOp :: CallbackRow () -> orig -> Ref Table -> impl Source #

impl ~ (TableCoordinate -> IO (Either NoChange ())) => Op (MoveCursor ()) Table orig impl Source # 
Instance details

Methods

runOp :: MoveCursor () -> orig -> Ref Table -> impl Source #

impl ~ (TableCoordinate -> TableCoordinate -> IO ()) => Op (SetSelection ()) Table orig impl Source # 
Instance details

Methods

runOp :: SetSelection () -> orig -> Ref Table -> impl Source #

impl ~ IO (TableCoordinate, TableCoordinate) => Op (GetSelection ()) Table orig impl Source # 
Instance details

Methods

runOp :: GetSelection () -> orig -> Ref Table -> impl Source #

impl ~ (TableCoordinate -> IO Bool) => Op (IsSelected ()) Table orig impl Source # 
Instance details

Methods

runOp :: IsSelected () -> orig -> Ref Table -> impl Source #

impl ~ IO Row => Op (GetTopRow ()) Table orig impl Source # 
Instance details

Methods

runOp :: GetTopRow () -> orig -> Ref Table -> impl Source #

impl ~ (Row -> IO ()) => Op (SetTopRow ()) Table orig impl Source # 
Instance details

Methods

runOp :: SetTopRow () -> orig -> Ref Table -> impl Source #

impl ~ IO Column => Op (GetColPosition ()) Table orig impl Source # 
Instance details

Methods

runOp :: GetColPosition () -> orig -> Ref Table -> impl Source #

impl ~ IO Row => Op (GetRowPosition ()) Table orig impl Source # 
Instance details

Methods

runOp :: GetRowPosition () -> orig -> Ref Table -> impl Source #

impl ~ (Column -> IO ()) => Op (SetColPosition ()) Table orig impl Source # 
Instance details

Methods

runOp :: SetColPosition () -> orig -> Ref Table -> impl Source #

impl ~ (Row -> IO ()) => Op (SetRowPosition ()) Table orig impl Source # 
Instance details

Methods

runOp :: SetRowPosition () -> orig -> Ref Table -> impl Source #

impl ~ (Int -> IO ()) => Op (SetColWidthAll ()) Table orig impl Source # 
Instance details

Methods

runOp :: SetColWidthAll () -> orig -> Ref Table -> impl Source #

impl ~ (Int -> IO ()) => Op (SetRowHeightAll ()) Table orig impl Source # 
Instance details

Methods

runOp :: SetRowHeightAll () -> orig -> Ref Table -> impl Source #

impl ~ (Column -> IO Int) => Op (GetColWidth ()) Table orig impl Source # 
Instance details

Methods

runOp :: GetColWidth () -> orig -> Ref Table -> impl Source #

impl ~ (Column -> Int -> IO ()) => Op (SetColWidth ()) Table orig impl Source # 
Instance details

Methods

runOp :: SetColWidth () -> orig -> Ref Table -> impl Source #

impl ~ (Row -> IO Int) => Op (GetRowHeight ()) Table orig impl Source # 
Instance details

Methods

runOp :: GetRowHeight () -> orig -> Ref Table -> impl Source #

impl ~ (Row -> Int -> IO ()) => Op (SetRowHeight ()) Table orig impl Source # 
Instance details

Methods

runOp :: SetRowHeight () -> orig -> Ref Table -> impl Source #

impl ~ IO Color => Op (GetColHeaderColor ()) Table orig impl Source # 
Instance details

Methods

runOp :: GetColHeaderColor () -> orig -> Ref Table -> impl Source #

impl ~ (Color -> IO ()) => Op (SetColHeaderColor ()) Table orig impl Source # 
Instance details

Methods

runOp :: SetColHeaderColor () -> orig -> Ref Table -> impl Source #

impl ~ IO Color => Op (GetRowHeaderColor ()) Table orig impl Source # 
Instance details

Methods

runOp :: GetRowHeaderColor () -> orig -> Ref Table -> impl Source #

impl ~ (Color -> IO ()) => Op (SetRowHeaderColor ()) Table orig impl Source # 
Instance details

Methods

runOp :: SetRowHeaderColor () -> orig -> Ref Table -> impl Source #

impl ~ IO Int => Op (GetRowHeaderWidth ()) Table orig impl Source # 
Instance details

Methods

runOp :: GetRowHeaderWidth () -> orig -> Ref Table -> impl Source #

impl ~ (Int -> IO ()) => Op (SetRowHeaderWidth ()) Table orig impl Source # 
Instance details

Methods

runOp :: SetRowHeaderWidth () -> orig -> Ref Table -> impl Source #

impl ~ IO Int => Op (GetColHeaderHeight ()) Table orig impl Source # 
Instance details

Methods

runOp :: GetColHeaderHeight () -> orig -> Ref Table -> impl Source #

impl ~ (Int -> IO ()) => Op (SetColHeaderHeight ()) Table orig impl Source # 
Instance details

Methods

runOp :: SetColHeaderHeight () -> orig -> Ref Table -> impl Source #

impl ~ (Bool -> IO ()) => Op (SetColHeader ()) Table orig impl Source # 
Instance details

Methods

runOp :: SetColHeader () -> orig -> Ref Table -> impl Source #

impl ~ IO Bool => Op (GetColHeader ()) Table orig impl Source # 
Instance details

Methods

runOp :: GetColHeader () -> orig -> Ref Table -> impl Source #

impl ~ (Bool -> IO ()) => Op (SetRowHeader ()) Table orig impl Source # 
Instance details

Methods

runOp :: SetRowHeader () -> orig -> Ref Table -> impl Source #

impl ~ IO Bool => Op (GetRowHeader ()) Table orig impl Source # 
Instance details

Methods

runOp :: GetRowHeader () -> orig -> Ref Table -> impl Source #

impl ~ (Int -> IO ()) => Op (SetRowResizeMin ()) Table orig impl Source # 
Instance details

Methods

runOp :: SetRowResizeMin () -> orig -> Ref Table -> impl Source #

impl ~ IO Int => Op (GetRowResizeMin ()) Table orig impl Source # 
Instance details

Methods

runOp :: GetRowResizeMin () -> orig -> Ref Table -> impl Source #

impl ~ (Int -> IO ()) => Op (SetColResizeMin ()) Table orig impl Source # 
Instance details

Methods

runOp :: SetColResizeMin () -> orig -> Ref Table -> impl Source #

impl ~ IO Int => Op (GetColResizeMin ()) Table orig impl Source # 
Instance details

Methods

runOp :: GetColResizeMin () -> orig -> Ref Table -> impl Source #

impl ~ (Bool -> IO ()) => Op (SetColResize ()) Table orig impl Source # 
Instance details

Methods

runOp :: SetColResize () -> orig -> Ref Table -> impl Source #

impl ~ IO Bool => Op (GetColResize ()) Table orig impl Source # 
Instance details

Methods

runOp :: GetColResize () -> orig -> Ref Table -> impl Source #

impl ~ (Bool -> IO ()) => Op (SetRowResize ()) Table orig impl Source # 
Instance details

Methods

runOp :: SetRowResize () -> orig -> Ref Table -> impl Source #

impl ~ IO Bool => Op (GetRowResize ()) Table orig impl Source # 
Instance details

Methods

runOp :: GetRowResize () -> orig -> Ref Table -> impl Source #

impl ~ IO Bool => Op (IsInteractiveResize ()) Table orig impl Source # 
Instance details

Methods

runOp :: IsInteractiveResize () -> orig -> Ref Table -> impl Source #

impl ~ IO (TableCoordinate, TableCoordinate) => Op (GetVisibleCells ()) Table orig impl Source # 
Instance details

Methods

runOp :: GetVisibleCells () -> orig -> Ref Table -> impl Source #

impl ~ IO Columns => Op (GetCols ()) Table orig impl Source # 
Instance details

Methods

runOp :: GetCols () -> orig -> Ref Table -> impl Source #

impl ~ (Columns -> IO ()) => Op (SetCols ()) Table orig impl Source # 
Instance details

Methods

runOp :: SetCols () -> orig -> Ref Table -> impl Source #

impl ~ IO Rows => Op (GetRows ()) Table orig impl Source # 
Instance details

Methods

runOp :: GetRows () -> orig -> Ref Table -> impl Source #

impl ~ (Rows -> IO ()) => Op (SetRows ()) Table orig impl Source # 
Instance details

Methods

runOp :: SetRows () -> orig -> Ref Table -> impl Source #

impl ~ IO Boxtype => Op (GetTableBox ()) Table orig impl Source # 
Instance details

Methods

runOp :: GetTableBox () -> orig -> Ref Table -> impl Source #

impl ~ (Boxtype -> IO ()) => Op (SetTableBox ()) Table orig impl Source # 
Instance details

Methods

runOp :: SetTableBox () -> orig -> Ref Table -> impl Source #

impl ~ (TableContext -> TableCoordinate -> IO ()) => Op (DoCallback ()) Table orig impl Source # 
Instance details

Methods

runOp :: DoCallback () -> orig -> Ref Table -> impl Source #

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

Methods

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

impl ~ IO () => Op (DrawSuper ()) Table orig impl Source # 
Instance details

Methods

runOp :: DrawSuper () -> orig -> Ref Table -> impl Source #

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

Methods

runOp :: GetChild () -> orig -> Ref Table -> impl Source #

impl ~ IO [Ref Widget] => Op (GetArray ()) Table orig impl Source # 
Instance details

Methods

runOp :: GetArray () -> orig -> Ref Table -> impl Source #

(Parent a Widget, Parent b Widget, impl ~ (Ref a -> Ref b -> IO ())) => Op (InsertBefore ()) Table orig impl Source # 
Instance details

Methods

runOp :: InsertBefore () -> orig -> Ref Table -> impl Source #

impl ~ IO Int => Op (Children ()) Table orig impl Source # 
Instance details

Methods

runOp :: Children () -> orig -> Ref Table -> impl Source #

impl ~ IO () => Op (InitSizes ()) Table orig impl Source # 
Instance details

Methods

runOp :: InitSizes () -> orig -> Ref Table -> impl Source #

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

Methods

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

(Parent a Widget, impl ~ (Ref a -> AtIndex -> IO ())) => Op (Insert ()) Table orig impl Source # 
Instance details

Methods

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

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

Methods

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

(Parent a Widget, impl ~ (Ref a -> IO Int)) => Op (Find ()) Table orig impl Source # 
Instance details

Methods

runOp :: Find () -> orig -> Ref Table -> impl Source #

impl ~ IO () => Op (End ()) Table orig impl Source # 
Instance details

Methods

runOp :: End () -> orig -> Ref Table -> impl Source #

impl ~ IO () => Op (Begin ()) Table orig impl Source # 
Instance details

Methods

runOp :: Begin () -> orig -> Ref Table -> impl Source #

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

Methods

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

impl ~ (Rectangle -> IO ()) => Op (ResizeSuper ()) Table orig impl Source # 
Instance details

Methods

runOp :: ResizeSuper () -> orig -> Ref Table -> impl Source #

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

Methods

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

impl ~ IO () => Op (HideSuper ()) Table orig impl Source # 
Instance details

Methods

runOp :: HideSuper () -> orig -> Ref Table -> impl Source #

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

Methods

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

impl ~ IO () => Op (ShowWidgetSuper ()) Table orig impl Source # 
Instance details

Methods

runOp :: ShowWidgetSuper () -> orig -> Ref Table -> impl Source #

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

Methods

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

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

Methods

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