module Data.Tree.NavigatableTree.XPathAxis
where
import Data.Maybe ( maybeToList )
import Data.Tree.NavigatableTree.Class
import Control.Arrow ( (>>>) )
import Control.Monad ( (>=>) )
maybeStar :: (a -> Maybe a) -> (a -> [a])
maybeStar f x = x : maybe [] (maybeStar f) (f x)
maybePlus :: (a -> Maybe a) -> (a -> [a])
maybePlus f x = maybe [] (maybeStar f) (f x)
parentAxis :: NavigatableTree t => t a -> [t a]
parentAxis = maybeToList . mvUp
ancestorAxis :: NavigatableTree t => t a -> [t a]
ancestorAxis = maybePlus mvUp
ancestorOrSelfAxis :: NavigatableTree t => t a -> [t a]
ancestorOrSelfAxis = maybeStar mvUp
childAxis :: NavigatableTree t => t a -> [t a]
childAxis = (mvDown >>> maybeToList) >=> maybeStar mvRight
descendantAxis :: NavigatableTree t => t a -> [t a]
descendantAxis = descendantOrSelfAxis >>> tail
descendantOrSelfAxis :: NavigatableTree t => t a -> [t a]
descendantOrSelfAxis = visit []
where
visit k t = t : maybe k (visit' k) (mvDown t)
visit' k t = visit (maybe k (visit' k) (mvRight t)) t
revDescendantOrSelfAxis :: NavigatableTree t => t a -> [t a]
revDescendantOrSelfAxis t
= t : concatMap revDescendantOrSelfAxis (reverse $ childAxis t)
followingSiblingAxis :: NavigatableTree t => t a -> [t a]
followingSiblingAxis = maybePlus mvRight
precedingSiblingAxis :: NavigatableTree t => t a -> [t a]
precedingSiblingAxis = maybePlus mvLeft
selfAxis :: NavigatableTree t => t a -> [t a]
selfAxis = (:[])
followingAxis :: NavigatableTree t => t a -> [t a]
followingAxis = ancestorOrSelfAxis >=> followingSiblingAxis >=> descendantOrSelfAxis
precedingAxis :: NavigatableTree t => t a -> [t a]
precedingAxis = ancestorOrSelfAxis >=> precedingSiblingAxis >=> revDescendantOrSelfAxis
mvToRoot :: NavigatableTree t => t a -> t a
mvToRoot = ancestorOrSelfAxis >>> last
isAtRoot :: NavigatableTree t => t a -> Bool
isAtRoot = null . ancestorAxis