module Graphics.UI.Gtk.Generics.TreeStore where import Graphics.UI.Gtk import Data.Tree {- Function to get the elements at each branch on the path to the element the user has selected. -} treeStoreGetActivatedElements :: TreeStore a -- ^ The TreeStore the user has selected from. -> TreePath -- ^ The path to the node selected by the user. -> IO [a] -- ^ The elements at each branch on the path to the selected node. treeStoreGetActivatedElements store path | null ( init path ) = treeStoreGetValue store path >>= (\r -> return [r] ) | otherwise = ( treeStoreGetValue store path ) >>= ( \l -> ( treeStoreGetActivatedElements store ( init path ) ) >>= ( \f -> return ( l : f ) ) ) {-| Function to find the path to a list of 'a' contained in a Forest, i.e. each element corresponds to the branch in the Forest (TreeStore) that matches the the corresponding element in the supplied list. -} findPath :: Eq a => Forest a -- ^ Forest of data. -> [a] -- ^ List containing elements to make a path. -> TreePath -- ^ Resulting path to elements of [a] findPath [] _ = [] findPath _ [] = [] findPath (x:xs) (y:ys) | rootLabel x == y = 0 : findPath ( subForest x ) ys | otherwise = case res of [] -> [] (z:[]) -> 1 + z : [] (z:zs) -> 1 + z : zs where res = findPath xs (y:ys)