{-# LANGUAGE RecordWildCards #-}
module XMonad.Util.TreeZipper(
TreeZipper(..)
, cursor
, fromForest
, toForest
, getSubForest
, rootNode
, parent
, children
, nextChild
, previousChild
, nodeDepth
, nodeIndex
, followPath
, findChild
, isLeaf
, isRoot
, isLast
, isFirst
) where
import Data.Tree
data TreeZipper a = TreeZipper { tz_current :: Tree a
, tz_before :: Forest a
, tz_after :: Forest a
, tz_parents :: [(Forest a, a, Forest a)]
}
cursor :: TreeZipper a -> a
cursor = rootLabel . tz_current
fromForest :: Forest a -> TreeZipper a
fromForest [] = error "XMonad.Util.TreeZipper.fromForest: can't create a TreeZipper from an empty list!"
fromForest (x:xs) = TreeZipper { tz_current = x
, tz_before = []
, tz_after = xs
, tz_parents = []
}
toForest :: TreeZipper a -> Forest a
toForest = getSubForest . rootNode
getSubForest :: TreeZipper a -> Forest a
getSubForest TreeZipper{..} = reverse tz_before ++ tz_current : tz_after
rootNode :: TreeZipper a -> TreeZipper a
rootNode = f
where
f z = maybe (g z) f $ parent z
g z = maybe z g $ previousChild z
parent :: TreeZipper a -> Maybe (TreeZipper a)
parent t = case tz_parents t of
(xs,a,ys) : ps -> Just
TreeZipper { tz_current = Node a (reverse (tz_before t) ++ tz_current t : tz_after t)
, tz_before = xs
, tz_after = ys
, tz_parents = ps
}
[] -> Nothing
children :: TreeZipper a -> Maybe (TreeZipper a)
children z = case subForest $ tz_current z of
(n:xs) -> Just
TreeZipper { tz_current = n
, tz_before = []
, tz_after = xs
, tz_parents = (tz_before z, cursor z, tz_after z) : tz_parents z
}
[] -> Nothing
nextChild :: TreeZipper a -> Maybe (TreeZipper a)
nextChild z = case tz_after z of
(n:xs) -> Just
TreeZipper { tz_current = n
, tz_before = tz_current z : tz_before z
, tz_after = xs
, tz_parents = tz_parents z
}
[] -> Nothing
previousChild :: TreeZipper a -> Maybe (TreeZipper a)
previousChild z = case tz_before z of
(n:xs) -> Just
TreeZipper { tz_current = n
, tz_before = xs
, tz_after = tz_current z : tz_after z
, tz_parents = tz_parents z
}
[] -> Nothing
nodeDepth :: TreeZipper a -> Int
nodeDepth = length . tz_parents
nodeIndex :: TreeZipper a -> Int
nodeIndex = length . tz_before
followPath :: Eq b => (a -> b) -> [b] -> TreeZipper a -> Maybe (TreeZipper a)
followPath _ [] z = Just z
followPath f [x] z = findChild (\y -> f y == x) z
followPath f (x:xs) z = findChild (\y -> f y == x) z >>= children >>= followPath f xs
findChild :: (a -> Bool) -> TreeZipper a -> Maybe (TreeZipper a)
findChild f z | f (cursor z) = Just z
| otherwise = nextChild z >>= findChild f
isLeaf :: TreeZipper a -> Bool
isLeaf = null . subForest . tz_current
isRoot :: TreeZipper a -> Bool
isRoot = null . tz_parents
isLast :: TreeZipper a -> Bool
isLast = null . tz_after
isFirst :: TreeZipper a -> Bool
isFirst = null . tz_before