| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Graphics.UI.FLTK.LowLevel.Table
Contents
- data TableCoordinate = TableCoordinate Row Column
- data Row = Row Int
- data Column = Column Int
- data CustomTableFuncs a = CustomTableFuncs {
- drawCellCustom :: Maybe (Ref a -> TableContext -> TableCoordinate -> Rectangle -> IO ())
- 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 () -> CustomTableFuncs a -> IO ()
- defaultCustomTableFuncs :: forall a. Parent a Table => CustomTableFuncs a
- tableCustom :: Rectangle -> Maybe String -> CustomWidgetFuncs Table -> CustomTableFuncs Table -> IO (Ref Table)
- tableCustomFunctionStruct :: (Parent a Widget, Parent b Table) => CustomWidgetFuncs a -> CustomTableFuncs b -> IO (Ptr ())
Documentation
data TableCoordinate Source
Constructors
| TableCoordinate Row Column |
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
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 () -> CustomTableFuncs a -> IO () Source
defaultCustomTableFuncs :: forall a. Parent a Table => CustomTableFuncs a Source
tableCustom :: Rectangle -> Maybe String -> CustomWidgetFuncs Table -> CustomTableFuncs Table -> IO (Ref Table) Source
tableCustomFunctionStruct :: (Parent a Widget, Parent b Table) => 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 a Widget) => Ref Table -> Ref a -> IO ())
callbackCol :: Ref Table -> IO Column
callbackContext :: Ref Table -> IO TableContext
callbackRow :: Ref Table -> IO Row
children :: Ref Table -> IO Int
clearSuper :: Ref Table -> IO ()
doCallback :: Ref Table -> TableContext -> Int -> Int -> IO ()
drawSuper :: 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 -> Int -> IO (Ref Widget)
getColHeader :: Ref Table -> IO Bool
getColHeaderColor :: Ref Table -> IO Color
getColHeaderHeight :: Ref Table -> IO Int
getColPosition :: Ref Table -> IO Int
getColResize :: Ref Table -> IO Int
getColResizeMin :: Ref Table -> IO Int
getColWidth :: Ref Table -> Int -> 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 -> Int -> IO Int
getRowPosition :: Ref Table -> IO Int
getRowResize :: Ref Table -> IO Int
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
handle :: Ref Table -> Event -> IO Int
hideSuper :: Ref Table -> IO ()
initSizes :: Ref Table -> IO ()
insert:: (Parent a Widget) => Ref Table -> Ref a -> Int -> IO ())
insertWithBefore:: (Parent a Widget, Parent b Widget) => Ref Table -> Ref a -> Ref b -> IO ())
isInteractiveResize :: Ref Table -> IO Int
isSelected :: Ref Table -> TableCoordinate -> IO Bool
moveCursor :: Ref Table -> Int -> Int -> 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 -> Int -> IO ()
setColResize :: Ref Table -> Bool -> IO ()
setColResizeMin :: Ref Table -> Int -> IO ()
setColWidth :: Ref Table -> Int -> 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 -> Int -> Int -> IO ()
setRowHeightAll :: Ref Table -> Int -> IO ()
setRowPosition :: Ref Table -> Int -> 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 ()
setVisibleCells :: Ref Table -> IO (TableCoordinate, TableCoordinate)