fltkhs-0.8.0.2: FLTK bindings

Safe HaskellNone
LanguageHaskell2010

Graphics.UI.FLTK.LowLevel.Base.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 WidgetBase) => Ref TableBase -> Ref a -> IO ()

begin :: Ref TableBase -> IO ()

callbackCol :: Ref TableBase -> IO (Column)

callbackContext :: Ref TableBase -> IO (TableContext)

callbackRow :: Ref TableBase -> IO (Row)

children :: Ref TableBase -> IO (Int)

clear :: Ref TableBase -> IO ()

destroy :: Ref TableBase -> IO ()

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

draw :: Ref TableBase -> IO ()

end :: Ref TableBase -> IO ()

find:: (Parent a WidgetBase) => Ref TableBase -> Ref a -> IO (Int)

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

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

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

getColHeader :: Ref TableBase -> IO (Bool)

getColHeaderColor :: Ref TableBase -> IO (Color)

getColHeaderHeight :: Ref TableBase -> IO (Int)

getColPosition :: Ref TableBase -> IO (Column)

getColResize :: Ref TableBase -> IO (Bool)

getColResizeMin :: Ref TableBase -> IO (Int)

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

getCols :: Ref TableBase -> IO (Columns)

getRowHeader :: Ref TableBase -> IO Bool

getRowHeaderColor :: Ref TableBase -> IO (Color)

getRowHeaderWidth :: Ref TableBase -> IO (Int)

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

getRowPosition :: Ref TableBase -> IO (Row)

getRowResize :: Ref TableBase -> IO (Bool)

getRowResizeMin :: Ref TableBase -> IO (Int)

getRows :: Ref TableBase -> IO (Rows)

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

getTabCellNav :: Ref TableBase -> IO (Bool)

getTableBox :: Ref TableBase -> IO (Boxtype)

getTopRow :: Ref TableBase -> IO (Row)

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

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

hide :: Ref TableBase -> IO ()

initSizes :: Ref TableBase -> IO ()

insert:: (Parent a WidgetBase) => Ref TableBase -> Ref a -> AtIndex -> IO ()

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

isInteractiveResize :: Ref TableBase -> IO (Bool)

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

showWidget :: Ref TableBase -> IO ()

Orphan instances

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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