Safe Haskell | None |
---|---|
Language | Haskell2010 |
- data TableCoordinate = TableCoordinate Row Column
- data Row = Row Int
- data Column = Column Int
- data CustomTableFuncs a = CustomTableFuncs {
- clearCustom :: Maybe (Ref a -> IO ())
- setRowsCustom :: Maybe (Ref a -> Int -> IO ())
- setColsCustom :: Maybe (Ref a -> Int -> IO ())
- mkSetInt :: (Ptr () -> CInt -> IO ()) -> IO (FunPtr (Ptr () -> CInt -> IO ()))
- mkDrawCell :: (Ptr () -> CInt -> CInt -> CInt -> CInt -> CInt -> CInt -> CInt -> IO ()) -> IO (FunPtr (Ptr () -> CInt -> CInt -> CInt -> CInt -> CInt -> CInt -> CInt -> IO ()))
- toSetIntPrim :: (Ref a -> Int -> IO ()) -> IO (FunPtr (Ptr () -> CInt -> IO ()))
- toDrawCellPrim :: (Ref a -> TableContext -> TableCoordinate -> Rectangle -> IO ()) -> IO (FunPtr (Ptr () -> CInt -> CInt -> CInt -> CInt -> CInt -> CInt -> CInt -> IO ()))
- fillCustomTableFunctionStruct :: forall a. Parent a Table => Ptr () -> Maybe (Ref a -> TableContext -> TableCoordinate -> Rectangle -> IO ()) -> CustomTableFuncs a -> IO ()
- defaultCustomTableFuncs :: forall a. Parent a Table => CustomTableFuncs a
- tableCustom :: Rectangle -> Maybe Text -> Maybe (Ref Table -> IO ()) -> (Ref Table -> TableContext -> TableCoordinate -> Rectangle -> IO ()) -> CustomWidgetFuncs Table -> CustomTableFuncs Table -> IO (Ref Table)
- tableCustomFunctionStruct :: (Parent a Widget, Parent b Table) => Maybe (Ref a -> IO ()) -> Maybe (Ref b -> TableContext -> TableCoordinate -> Rectangle -> IO ()) -> CustomWidgetFuncs a -> CustomTableFuncs b -> IO (Ptr ())
Documentation
data CustomTableFuncs a Source #
CustomTableFuncs | |
|
mkDrawCell :: (Ptr () -> CInt -> CInt -> CInt -> CInt -> CInt -> CInt -> CInt -> IO ()) -> IO (FunPtr (Ptr () -> CInt -> CInt -> CInt -> CInt -> CInt -> CInt -> CInt -> IO ())) Source #
toDrawCellPrim :: (Ref a -> TableContext -> TableCoordinate -> Rectangle -> IO ()) -> IO (FunPtr (Ptr () -> CInt -> CInt -> CInt -> CInt -> CInt -> CInt -> CInt -> IO ())) Source #
fillCustomTableFunctionStruct :: forall a. Parent a Table => Ptr () -> Maybe (Ref a -> TableContext -> TableCoordinate -> Rectangle -> IO ()) -> CustomTableFuncs a -> IO () Source #
defaultCustomTableFuncs :: forall a. Parent a Table => CustomTableFuncs a Source #
:: 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) |
tableCustomFunctionStruct :: (Parent a Widget, Parent b Table) => Maybe (Ref a -> IO ()) -> Maybe (Ref b -> TableContext -> TableCoordinate -> Rectangle -> IO ()) -> CustomWidgetFuncs a -> CustomTableFuncs b -> IO (Ptr ()) Source #
Hierarchy
Graphics.UI.FLTK.LowLevel.Widget | v Graphics.UI.FLTK.LowLevel.Group | v Graphics.UI.FLTK.LowLevel.Table
Table functions
add:: (Parent
aWidget
) =>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
aWidget
) =>Ref
Table
->Ref
a ->IO
(Int
) findCell ::Ref
Table
->TableContext
->TableCoordinate
->IO
(Maybe
Rectangle
) getArray ::Ref
Table
->IO
[Ref
Widget
] getChild ::Ref
Table
->Int
->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
(Int
) 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
(Int
) getSelection ::Ref
Table
->IO
(TableCoordinate
,TableCoordinate
) getTableBox ::Ref
Table
->IO
(Boxtype
) getTopRow ::Ref
Table
->IO
(Row
) getVisibleCells ::Ref
Table
->IO
('TableCoordinate,TableCoordinate') handle ::Ref
Table
->Event
->IO
(Int
) hide ::Ref
Table
->IO
() hideSuper ::Ref
Table
->IO
() initSizes ::Ref
Table
->IO
() insert:: (Parent
aWidget
) =>Ref
Table
->Ref
a ->Int
->IO
() insertWithBefore:: (Parent
aWidget
,Parent
bWidget
) =>Ref
Table
->Ref
a ->Ref
b ->IO
() isInteractiveResize ::Ref
Table
->IO
(Bool
) isSelected ::Ref
Table
->TableCoordinate
->IO
Bool
moveCursor ::Ref
Table
->TableCoordinate
->IO
(Int
) 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
->Int
->IO
() setColsSuper ::Ref
Table
->Int
->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
->Int
->IO
() setRowsSuper ::Ref
Table
->Int
->IO
() setSelection ::Ref
Table
->Int
->Int
->Int
->Int
->IO
() setTableBox ::Ref
Table
->Boxtype
->IO
() setTopRow ::Ref
Table
->Row
->IO
() showWidget ::Ref
Table
->IO
() showWidgetSuper ::Ref
Table
->IO
()
Orphan instances
(~) * impl (Int -> IO ()) => Op (SetColsSuper ()) Table orig impl Source # | |
(~) * impl (Int -> IO ()) => Op (SetRowsSuper ()) Table orig impl Source # | |
(~) * impl (IO ()) => Op (ClearSuper ()) Table orig impl Source # | |
(~) * impl (TableContext -> TableCoordinate -> IO (Maybe Rectangle)) => Op (FindCell ()) Table orig impl Source # | |
(~) * impl (IO TableContext) => Op (CallbackContext ()) Table orig impl Source # | |
(~) * impl (IO Column) => Op (CallbackCol ()) Table orig impl Source # | |
(~) * impl (IO Row) => Op (CallbackRow ()) Table orig impl Source # | |
(~) * impl (TableCoordinate -> IO Int) => Op (MoveCursor ()) Table orig impl Source # | |
(~) * impl (Int -> Int -> Int -> Int -> IO ()) => Op (SetSelection ()) Table orig impl Source # | |
(~) * impl (IO (TableCoordinate, TableCoordinate)) => Op (GetSelection ()) Table orig impl Source # | |
(~) * impl (TableCoordinate -> IO Bool) => Op (IsSelected ()) Table orig impl Source # | |
(~) * impl (IO Row) => Op (GetTopRow ()) Table orig impl Source # | |
(~) * impl (Row -> IO ()) => Op (SetTopRow ()) Table orig impl Source # | |
(~) * impl (IO Column) => Op (GetColPosition ()) Table orig impl Source # | |
(~) * impl (IO Row) => Op (GetRowPosition ()) Table orig impl Source # | |
(~) * impl (Column -> IO ()) => Op (SetColPosition ()) Table orig impl Source # | |
(~) * impl (Row -> IO ()) => Op (SetRowPosition ()) Table orig impl Source # | |
(~) * impl (Int -> IO ()) => Op (SetColWidthAll ()) Table orig impl Source # | |
(~) * impl (Int -> IO ()) => Op (SetRowHeightAll ()) Table orig impl Source # | |
(~) * impl (Column -> IO Int) => Op (GetColWidth ()) Table orig impl Source # | |
(~) * impl (Column -> Int -> IO ()) => Op (SetColWidth ()) Table orig impl Source # | |
(~) * impl (Row -> IO Int) => Op (GetRowHeight ()) Table orig impl Source # | |
(~) * impl (Row -> Int -> IO ()) => Op (SetRowHeight ()) Table orig impl Source # | |
(~) * impl (IO Color) => Op (GetColHeaderColor ()) Table orig impl Source # | |
(~) * impl (Color -> IO ()) => Op (SetColHeaderColor ()) Table orig impl Source # | |
(~) * impl (IO Color) => Op (GetRowHeaderColor ()) Table orig impl Source # | |
(~) * impl (Color -> IO ()) => Op (SetRowHeaderColor ()) Table orig impl Source # | |
(~) * impl (IO Int) => Op (GetRowHeaderWidth ()) Table orig impl Source # | |
(~) * impl (Int -> IO ()) => Op (SetRowHeaderWidth ()) Table orig impl Source # | |
(~) * impl (IO Int) => Op (GetColHeaderHeight ()) Table orig impl Source # | |
(~) * impl (Int -> IO ()) => Op (SetColHeaderHeight ()) Table orig impl Source # | |
(~) * impl (Bool -> IO ()) => Op (SetColHeader ()) Table orig impl Source # | |
(~) * impl (IO Bool) => Op (GetColHeader ()) Table orig impl Source # | |
(~) * impl (Bool -> IO ()) => Op (SetRowHeader ()) Table orig impl Source # | |
(~) * impl (IO Bool) => Op (GetRowHeader ()) Table orig impl Source # | |
(~) * impl (Int -> IO ()) => Op (SetRowResizeMin ()) Table orig impl Source # | |
(~) * impl (IO Int) => Op (GetRowResizeMin ()) Table orig impl Source # | |
(~) * impl (Int -> IO ()) => Op (SetColResizeMin ()) Table orig impl Source # | |
(~) * impl (IO Int) => Op (GetColResizeMin ()) Table orig impl Source # | |
(~) * impl (Bool -> IO ()) => Op (SetColResize ()) Table orig impl Source # | |
(~) * impl (IO Bool) => Op (GetColResize ()) Table orig impl Source # | |
(~) * impl (Bool -> IO ()) => Op (SetRowResize ()) Table orig impl Source # | |
(~) * impl (IO Bool) => Op (GetRowResize ()) Table orig impl Source # | |
(~) * impl (IO Bool) => Op (IsInteractiveResize ()) Table orig impl Source # | |
(~) * impl (IO (TableCoordinate, TableCoordinate)) => Op (GetVisibleCells ()) Table orig impl Source # | |
(~) * impl (IO Int) => Op (GetCols ()) Table orig impl Source # | |
(~) * impl (Int -> IO ()) => Op (SetCols ()) Table orig impl Source # | |
(~) * impl (IO Int) => Op (GetRows ()) Table orig impl Source # | |
(~) * impl (Int -> IO ()) => Op (SetRows ()) Table orig impl Source # | |
(~) * impl (IO Boxtype) => Op (GetTableBox ()) Table orig impl Source # | |
(~) * impl (Boxtype -> IO ()) => Op (SetTableBox ()) Table orig impl Source # | |
(~) * impl (TableContext -> TableCoordinate -> IO ()) => Op (DoCallback ()) Table orig impl Source # | |
(~) * impl (IO ()) => Op (Draw ()) Table orig impl Source # | |
(~) * impl (IO ()) => Op (DrawSuper ()) Table orig impl Source # | |
(~) * impl (Int -> IO (Maybe (Ref Widget))) => Op (GetChild ()) Table orig impl Source # | |
(~) * impl (IO [Ref Widget]) => Op (GetArray ()) Table orig impl Source # | |
(Parent a Widget, Parent b Widget, (~) * impl (Ref a -> Ref b -> IO ())) => Op (InsertWithBefore ()) Table orig impl Source # | |
(~) * impl (IO Int) => Op (Children ()) Table orig impl Source # | |
(~) * impl (IO ()) => Op (InitSizes ()) Table orig impl Source # | |
(~) * impl (IO ()) => Op (Clear ()) Table orig impl Source # | |
(Parent a Widget, (~) * impl (Ref a -> Int -> IO ())) => Op (Insert ()) Table orig impl Source # | |
(Parent a Widget, (~) * impl (Ref a -> IO ())) => Op (Add ()) Table orig impl Source # | |
(Parent a Widget, (~) * impl (Ref a -> IO Int)) => Op (Find ()) Table orig impl Source # | |
(~) * impl (IO ()) => Op (End ()) Table orig impl Source # | |
(~) * impl (IO ()) => Op (Begin ()) Table orig impl Source # | |
(~) * impl (Rectangle -> IO ()) => Op (Resize ()) Table orig impl Source # | |
(~) * impl (Rectangle -> IO ()) => Op (ResizeSuper ()) Table orig impl Source # | |
(~) * impl (IO ()) => Op (Hide ()) Table orig impl Source # | |
(~) * impl (IO ()) => Op (HideSuper ()) Table orig impl Source # | |
(~) * impl (IO ()) => Op (ShowWidget ()) Table orig impl Source # | |
(~) * impl (IO ()) => Op (ShowWidgetSuper ()) Table orig impl Source # | |
(~) * impl (Event -> IO (Either UnknownEvent ())) => Op (Handle ()) Table orig impl Source # | |
(~) * impl (IO ()) => Op (Destroy ()) Table orig impl Source # | |