module Graphics.UI.Gtk.ModelView.TreeSelection (
TreeSelection,
TreeSelectionClass,
castToTreeSelection, gTypeTreeSelection,
toTreeSelection,
SelectionMode(..),
TreeSelectionCB,
TreeSelectionForeachCB,
treeSelectionSetMode,
treeSelectionGetMode,
treeSelectionSetSelectFunction,
treeSelectionGetTreeView,
treeSelectionGetSelected,
treeSelectionSelectedForeach,
treeSelectionGetSelectedRows,
treeSelectionCountSelectedRows,
treeSelectionSelectPath,
treeSelectionUnselectPath,
treeSelectionPathIsSelected,
treeSelectionSelectIter,
treeSelectionUnselectIter,
treeSelectionIterIsSelected,
treeSelectionSelectAll,
treeSelectionUnselectAll,
treeSelectionSelectRange,
treeSelectionUnselectRange,
treeSelectionMode,
treeSelectionSelectionChanged,
) where
import Control.Monad (liftM)
import System.Glib.FFI
import System.Glib.GList (fromGList)
import System.Glib.Attributes
import Graphics.UI.Gtk.Abstract.Object (makeNewObject)
import Graphics.UI.Gtk.Types
import Graphics.UI.Gtk.Signals
import Graphics.UI.Gtk.General.Enums (SelectionMode(..))
import Graphics.UI.Gtk.ModelView.TreeModel
import Graphics.UI.Gtk.ModelView.Types
treeSelectionSetMode :: TreeSelectionClass self => self
-> SelectionMode
-> IO ()
treeSelectionSetMode self type_ =
(\(TreeSelection arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_tree_selection_set_mode argPtr1 arg2)
(toTreeSelection self)
((fromIntegral . fromEnum) type_)
treeSelectionGetMode :: TreeSelectionClass self => self
-> IO SelectionMode
treeSelectionGetMode self =
liftM (toEnum . fromIntegral) $
(\(TreeSelection arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_tree_selection_get_mode argPtr1)
(toTreeSelection self)
treeSelectionSetSelectFunction :: TreeSelectionClass self => self
-> TreeSelectionCB -> IO ()
treeSelectionSetSelectFunction ts fun = do
fPtr <- mkTreeSelectionFunc (\_ _ tp _ _ -> do
path <- peekTreePath (castPtr tp)
liftM fromBool $ fun path
)
(\(TreeSelection arg1) arg2 arg3 arg4 -> withForeignPtr arg1 $ \argPtr1 ->gtk_tree_selection_set_select_function argPtr1 arg2 arg3 arg4)
(toTreeSelection ts)
fPtr
(castFunPtrToPtr fPtr)
destroyFunPtr
type TreeSelectionCB = TreePath -> IO Bool
type TreeSelectionFunc = FunPtr (((Ptr TreeSelection) -> ((Ptr TreeModel) -> ((Ptr NativeTreePath) -> (CInt -> ((Ptr ()) -> (IO CInt)))))))
foreign import ccall "wrapper" mkTreeSelectionFunc ::
(Ptr TreeSelection -> Ptr TreeModel -> Ptr NativeTreePath -> (CInt) -> Ptr () -> IO CInt)->
IO TreeSelectionFunc
treeSelectionGetTreeView :: TreeSelectionClass self => self -> IO TreeView
treeSelectionGetTreeView self =
makeNewObject mkTreeView $
(\(TreeSelection arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_tree_selection_get_tree_view argPtr1)
(toTreeSelection self)
treeSelectionGetSelected :: TreeSelectionClass self => self ->
IO (Maybe TreeIter)
treeSelectionGetSelected self =
receiveTreeIter $ \iterPtr ->
(\(TreeSelection arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->gtk_tree_selection_get_selected argPtr1 arg2 arg3)
(toTreeSelection self)
nullPtr
iterPtr
treeSelectionSelectedForeach :: TreeSelectionClass self => self
-> TreeSelectionForeachCB
-> IO ()
treeSelectionSelectedForeach self fun = do
fPtr <- mkTreeSelectionForeachFunc (\_ _ iterPtr _ -> do
iter <- peek iterPtr
fun iter
)
(\(TreeSelection arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->gtk_tree_selection_selected_foreach argPtr1 arg2 arg3)
(toTreeSelection self)
fPtr
nullPtr
freeHaskellFunPtr fPtr
type TreeSelectionForeachCB = TreeIter -> IO ()
type TreeSelectionForeachFunc = FunPtr (((Ptr TreeModel) -> ((Ptr NativeTreePath) -> ((Ptr TreeIter) -> ((Ptr ()) -> (IO ()))))))
foreign import ccall "wrapper" mkTreeSelectionForeachFunc ::
(Ptr TreeModel -> Ptr NativeTreePath -> Ptr TreeIter -> Ptr () -> IO ()) -> IO TreeSelectionForeachFunc
treeSelectionGetSelectedRows :: TreeSelectionClass self => self
-> IO [TreePath]
treeSelectionGetSelectedRows self =
(\(TreeSelection arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_tree_selection_get_selected_rows argPtr1 arg2)
(toTreeSelection self)
nullPtr
>>= fromGList
>>= mapM fromTreePath
treeSelectionCountSelectedRows :: TreeSelectionClass self => self
-> IO Int
treeSelectionCountSelectedRows self =
liftM fromIntegral $
(\(TreeSelection arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_tree_selection_count_selected_rows argPtr1)
(toTreeSelection self)
treeSelectionSelectPath :: TreeSelectionClass self => self
-> TreePath
-> IO ()
treeSelectionSelectPath self [] = return ()
treeSelectionSelectPath self path =
withTreePath path $ \path ->
(\(TreeSelection arg1) (NativeTreePath arg2) -> withForeignPtr arg1 $ \argPtr1 ->gtk_tree_selection_select_path argPtr1 arg2)
(toTreeSelection self)
path
treeSelectionUnselectPath :: TreeSelectionClass self => self
-> TreePath
-> IO ()
treeSelectionUnselectPath self path =
withTreePath path $ \path ->
(\(TreeSelection arg1) (NativeTreePath arg2) -> withForeignPtr arg1 $ \argPtr1 ->gtk_tree_selection_unselect_path argPtr1 arg2)
(toTreeSelection self)
path
treeSelectionPathIsSelected :: TreeSelectionClass self => self
-> TreePath -> IO Bool
treeSelectionPathIsSelected self path =
liftM toBool $
withTreePath path $ \path ->
(\(TreeSelection arg1) (NativeTreePath arg2) -> withForeignPtr arg1 $ \argPtr1 ->gtk_tree_selection_path_is_selected argPtr1 arg2)
(toTreeSelection self)
path
treeSelectionSelectIter :: TreeSelectionClass self => self -> TreeIter -> IO ()
treeSelectionSelectIter self iter =
with iter $ \iterPtr ->
(\(TreeSelection arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_tree_selection_select_iter argPtr1 arg2)
(toTreeSelection self)
iterPtr
treeSelectionUnselectIter :: TreeSelectionClass self => self -> TreeIter -> IO ()
treeSelectionUnselectIter self iter =
with iter $ \iterPtr ->
(\(TreeSelection arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_tree_selection_unselect_iter argPtr1 arg2)
(toTreeSelection self)
iterPtr
treeSelectionIterIsSelected :: TreeSelectionClass self => self
-> TreeIter
-> IO Bool
treeSelectionIterIsSelected self iter =
liftM toBool $
with iter $ \iterPtr ->
(\(TreeSelection arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_tree_selection_iter_is_selected argPtr1 arg2)
(toTreeSelection self)
iterPtr
treeSelectionSelectAll :: TreeSelectionClass self => self -> IO ()
treeSelectionSelectAll self =
(\(TreeSelection arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_tree_selection_select_all argPtr1)
(toTreeSelection self)
treeSelectionUnselectAll :: TreeSelectionClass self => self -> IO ()
treeSelectionUnselectAll self =
(\(TreeSelection arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_tree_selection_unselect_all argPtr1)
(toTreeSelection self)
treeSelectionSelectRange :: TreeSelectionClass self => self
-> TreePath
-> TreePath
-> IO ()
treeSelectionSelectRange self startPath endPath =
withTreePath endPath $ \endPath ->
withTreePath startPath $ \startPath ->
(\(TreeSelection arg1) (NativeTreePath arg2) (NativeTreePath arg3) -> withForeignPtr arg1 $ \argPtr1 ->gtk_tree_selection_select_range argPtr1 arg2 arg3)
(toTreeSelection self)
startPath
endPath
treeSelectionUnselectRange :: TreeSelectionClass self => self
-> TreePath
-> TreePath
-> IO ()
treeSelectionUnselectRange self startPath endPath =
withTreePath endPath $ \endPath ->
withTreePath startPath $ \startPath ->
(\(TreeSelection arg1) (NativeTreePath arg2) (NativeTreePath arg3) -> withForeignPtr arg1 $ \argPtr1 ->gtk_tree_selection_unselect_range argPtr1 arg2 arg3)
(toTreeSelection self)
startPath
endPath
treeSelectionMode :: TreeSelectionClass self => Attr self SelectionMode
treeSelectionMode = newAttr
treeSelectionGetMode
treeSelectionSetMode
treeSelectionSelectionChanged :: TreeSelectionClass self => Signal self (IO ())
treeSelectionSelectionChanged = Signal (connect_NONE__NONE "changed")
foreign import ccall safe "gtk_tree_selection_set_mode"
gtk_tree_selection_set_mode :: ((Ptr TreeSelection) -> (CInt -> (IO ())))
foreign import ccall unsafe "gtk_tree_selection_get_mode"
gtk_tree_selection_get_mode :: ((Ptr TreeSelection) -> (IO CInt))
foreign import ccall safe "gtk_tree_selection_set_select_function"
gtk_tree_selection_set_select_function :: ((Ptr TreeSelection) -> ((FunPtr ((Ptr TreeSelection) -> ((Ptr TreeModel) -> ((Ptr NativeTreePath) -> (CInt -> ((Ptr ()) -> (IO CInt))))))) -> ((Ptr ()) -> ((FunPtr ((Ptr ()) -> (IO ()))) -> (IO ())))))
foreign import ccall unsafe "gtk_tree_selection_get_tree_view"
gtk_tree_selection_get_tree_view :: ((Ptr TreeSelection) -> (IO (Ptr TreeView)))
foreign import ccall safe "gtk_tree_selection_get_selected"
gtk_tree_selection_get_selected :: ((Ptr TreeSelection) -> ((Ptr TreeModel) -> ((Ptr TreeIter) -> (IO CInt))))
foreign import ccall safe "gtk_tree_selection_selected_foreach"
gtk_tree_selection_selected_foreach :: ((Ptr TreeSelection) -> ((FunPtr ((Ptr TreeModel) -> ((Ptr NativeTreePath) -> ((Ptr TreeIter) -> ((Ptr ()) -> (IO ())))))) -> ((Ptr ()) -> (IO ()))))
foreign import ccall safe "gtk_tree_selection_get_selected_rows"
gtk_tree_selection_get_selected_rows :: ((Ptr TreeSelection) -> ((Ptr TreeModel) -> (IO (Ptr ()))))
foreign import ccall safe "gtk_tree_selection_count_selected_rows"
gtk_tree_selection_count_selected_rows :: ((Ptr TreeSelection) -> (IO CInt))
foreign import ccall safe "gtk_tree_selection_select_path"
gtk_tree_selection_select_path :: ((Ptr TreeSelection) -> ((Ptr NativeTreePath) -> (IO ())))
foreign import ccall safe "gtk_tree_selection_unselect_path"
gtk_tree_selection_unselect_path :: ((Ptr TreeSelection) -> ((Ptr NativeTreePath) -> (IO ())))
foreign import ccall safe "gtk_tree_selection_path_is_selected"
gtk_tree_selection_path_is_selected :: ((Ptr TreeSelection) -> ((Ptr NativeTreePath) -> (IO CInt)))
foreign import ccall safe "gtk_tree_selection_select_iter"
gtk_tree_selection_select_iter :: ((Ptr TreeSelection) -> ((Ptr TreeIter) -> (IO ())))
foreign import ccall safe "gtk_tree_selection_unselect_iter"
gtk_tree_selection_unselect_iter :: ((Ptr TreeSelection) -> ((Ptr TreeIter) -> (IO ())))
foreign import ccall safe "gtk_tree_selection_iter_is_selected"
gtk_tree_selection_iter_is_selected :: ((Ptr TreeSelection) -> ((Ptr TreeIter) -> (IO CInt)))
foreign import ccall safe "gtk_tree_selection_select_all"
gtk_tree_selection_select_all :: ((Ptr TreeSelection) -> (IO ()))
foreign import ccall safe "gtk_tree_selection_unselect_all"
gtk_tree_selection_unselect_all :: ((Ptr TreeSelection) -> (IO ()))
foreign import ccall safe "gtk_tree_selection_select_range"
gtk_tree_selection_select_range :: ((Ptr TreeSelection) -> ((Ptr NativeTreePath) -> ((Ptr NativeTreePath) -> (IO ()))))
foreign import ccall safe "gtk_tree_selection_unselect_range"
gtk_tree_selection_unselect_range :: ((Ptr TreeSelection) -> ((Ptr NativeTreePath) -> ((Ptr NativeTreePath) -> (IO ()))))