{-# LANGUAGE ForeignFunctionInterface #-} module Graphics.UI.FLTK.Browser (Browser, Browser_C(..), add, insert, clear, bottomline, middleline, topline, columnChar, formatChar, columnWidths, move, remove, size, newBrowser ) where import Graphics.UI.FLTK.Widget import Foreign.C.String import Foreign -- | The type for Browsers, which is a subtype of Widget. newtype Browser = Browser (Ptr Browser) instance Widget_C Browser where _widget (Browser p) = castPtr p -- | Class for Browsers. class Browser_C a where _browser :: a -> Ptr Browser instance Browser_C Browser where _browser (Browser b) = b foreign import ccall "Fl_Browser_new" _newBrowser :: Int->Int->Int->Int->IO Browser -- | Create a new browser. newBrowser :: Int->Int->Int->Int->[Prop Browser]->IO Browser newBrowser x y w h l = do b <- _newBrowser x y w h set b l return b foreign import ccall "fl_Browser_add" _add :: Ptr Browser -> CString -> IO () foreign import ccall "fl_Browser_insert" _insert :: Ptr Browser->Int->CString -> IO () foreign import ccall "fl_Browser_clear" _clear :: Ptr Browser -> IO () foreign import ccall "fl_Browser_bottomline" _bottomline :: Ptr Browser-> Int -> IO () foreign import ccall "fl_Browser_middleline" _middleline :: Ptr Browser-> Int -> IO () foreign import ccall "fl_Browser_topline" _topline :: Ptr Browser -> Int -> IO () -- | Add a new row to the browser. add :: Browser_C c => c -> String -> IO () add b s = withCString s (\cs -> _add (_browser b) cs) -- | Insert a new row at the specified position. Indeces start at 1. insert :: Browser_C c => c -> Int -> String -> IO () insert b i s = withCString s (\cs -> _insert (_browser b) i cs) -- | Delete all rows from the browser. clear :: Browser_C c => c -> IO () clear = _clear . _browser bottomline, middleline, topline :: Browser_C c => c -> Int -> IO () -- | Set the bottomline of the browser to the specified row index. bottomline = _bottomline . _browser -- | Set the middleline of the browser to the specified row index. middleline = _middleline . _browser -- | Set the topline of the browser to the specified row index. topline = _topline . _browser foreign import ccall "fl_Browser_column_char_AS" _colC_AS :: Ptr Browser->Char-> IO () foreign import ccall "fl_Browser_column_char_AG" _colC_AG :: Ptr Browser->IO Char foreign import ccall "fl_Browser_format_char_AS" _forC_AS :: Ptr Browser->Char->IO () foreign import ccall "fl_Browser_format_char_AG" _forC_AG :: Ptr Browser->IO Char foreign import ccall "fl_Browser_column_widths_AS" _colW_AS :: Ptr Browser -> Ptr Int -> IO () foreign import ccall "fl_Browser_column_widths_AG" _colW_AG :: Ptr Browser -> IO (Ptr Int) columnChar, formatChar :: Browser_C b => Attr b Char -- | Column-separator character. The default is \'\\t\'. columnChar = Attr (_colC_AG . _browser) (\b v -> _colC_AS (_browser b) v) -- | Format character. The default is \'\@\'. formatChar = Attr (_forC_AG . _browser) (\b v -> _forC_AS (_browser b) v) -- | Column widths as pixels. columnWidths :: Browser_C b => Attr b [Int] columnWidths = Attr (\c -> _colW_AG (_browser c) >>= peekArray0 0) (\b v -> withArray0 0 v (\ia -> _colW_AS (_browser b) ia)) foreign import ccall "fl_Browser_move" _move :: Ptr Browser -> Int -> Int -> IO () foreign import ccall "fl_Browser_remove" _remove :: Ptr Browser -> Int -> IO () foreign import ccall "fl_Browser_size" _size :: Ptr Browser -> IO Int -- | Move a row in the browser. move :: Browser_C c => c -> Int -> Int -> IO () move = _move . _browser -- | Remove a row in the browser. remove :: Browser_C c => c -> Int -> IO () remove = _remove . _browser -- | Return the number of rows in the browser. size :: Browser_C c => c -> IO Int size = _size . _browser