module Control.Arrow.ArrowNavigatableTree
where
import Control.Arrow
import Control.Arrow.ArrowList
import Control.Arrow.ArrowIf
import Data.Maybe
import Data.Tree.NavigatableTree.Class ( NavigatableTree
, NavigatableTreeToTree
, NavigatableTreeModify
)
import qualified Data.Tree.NavigatableTree.Class as T
import qualified Data.Tree.NavigatableTree.XPathAxis as T
class (ArrowList a) => ArrowNavigatableTree a where
moveUp :: NavigatableTree t => a (t b) (t b)
moveUp = arrL $ maybeToList . T.mvUp
moveDown :: NavigatableTree t => a (t b) (t b)
moveDown = arrL $ maybeToList . T.mvDown
moveLeft :: NavigatableTree t => a (t b) (t b)
moveLeft = arrL $ maybeToList . T.mvLeft
moveRight :: NavigatableTree t => a (t b) (t b)
moveRight = arrL $ maybeToList . T.mvRight
parentAxis :: (ArrowList a, NavigatableTree t) => a (t b) (t b)
parentAxis = arrL T.parentAxis
ancestorAxis :: (ArrowList a, NavigatableTree t) => a (t b) (t b)
ancestorAxis = arrL T.ancestorAxis
ancestorOrSelfAxis :: (ArrowList a, NavigatableTree t) => a (t b) (t b)
ancestorOrSelfAxis = arrL T.ancestorOrSelfAxis
childAxis :: (ArrowList a, NavigatableTree t) => a (t b) (t b)
childAxis = arrL T.childAxis
descendantAxis :: (ArrowList a, NavigatableTree t) => a (t b) (t b)
descendantAxis = arrL T.descendantAxis
descendantOrSelfAxis :: (ArrowList a, NavigatableTree t) => a (t b) (t b)
descendantOrSelfAxis = arrL T.descendantOrSelfAxis
descendantOrFollowingAxis :: (ArrowList a, NavigatableTree t) => a (t b) (t b)
descendantOrFollowingAxis = descendantAxis <+> followingAxis
revDescendantOrSelfAxis :: (ArrowList a, NavigatableTree t) => a (t b) (t b)
revDescendantOrSelfAxis = arrL T.revDescendantOrSelfAxis
followingSiblingAxis :: (ArrowList a, NavigatableTree t) => a (t b) (t b)
followingSiblingAxis = arrL T.followingSiblingAxis
precedingSiblingAxis :: (ArrowList a, NavigatableTree t) => a (t b) (t b)
precedingSiblingAxis = arrL T.precedingSiblingAxis
selfAxis :: (ArrowList a, NavigatableTree t) => a (t b) (t b)
selfAxis = arrL T.selfAxis
followingAxis :: (ArrowList a, NavigatableTree t) => a (t b) (t b)
followingAxis = arrL T.followingAxis
precedingAxis :: (ArrowList a, NavigatableTree t) => a (t b) (t b)
precedingAxis = arrL T.precedingAxis
moveToRoot :: (Arrow a, NavigatableTree t) => a (t b) (t b)
moveToRoot = arr T.mvToRoot
isAtRoot :: (ArrowList a, NavigatableTree t) => a (t b) (t b)
isAtRoot = isA (null . T.ancestorAxis)
addNav :: ( ArrowList a
, NavigatableTreeToTree nt t
) =>
a (t b) (nt b)
addNav = arr T.fromTree
remNav :: ( ArrowList a
, NavigatableTreeToTree nt t
) =>
a (nt b) (t b)
remNav = arr T.toTree
withNav :: ( ArrowList a
, NavigatableTreeToTree nt t
) =>
a (nt b) (nt c) -> a (t b) (t c)
withNav f = addNav >>> f >>> remNav
withoutNav :: ( ArrowList a
, NavigatableTreeToTree nt t
, NavigatableTreeModify nt t
) =>
a (t b) (t b) -> a (nt b) (nt b)
withoutNav f = ( (remNav >>> f)
&&&
this
)
>>> arr (uncurry T.substThisTree)
filterAxis :: ( ArrowIf a
, NavigatableTreeToTree nt t
) =>
a (t b) c -> a (nt b) (nt b)
filterAxis p = (remNav >>> p) `guards` this
moveOn :: ( ArrowList a
, NavigatableTree t
) =>
a (t b) (t b) -> a (t b) (t b)
moveOn axis = single $ axis
changeThisTree :: ( ArrowList a
, ArrowIf a
, NavigatableTreeToTree nt t
, NavigatableTreeModify nt t
) =>
a (t b) (t b) -> a (nt b) (nt b)
changeThisTree cf = withoutNav $ single cf `orElse` this
substThisTree :: ( ArrowList a
, ArrowIf a
, NavigatableTreeToTree nt t
, NavigatableTreeModify nt t
) =>
t b -> a (nt b) (nt b)
substThisTree t = changeThisTree (constA t)
addToTheLeft :: ( ArrowList a
, NavigatableTreeToTree nt t
, NavigatableTreeModify nt t
) =>
a (t b) (t b) -> a (nt b) (nt b)
addToTheLeft = addToOneSide $
foldl (\ acc t -> acc >>= T.addTreeLeft t)
addToTheRight :: ( ArrowList a
, NavigatableTreeToTree nt t
, NavigatableTreeModify nt t
) =>
a (t b) (t b) -> a (nt b) (nt b)
addToTheRight = addToOneSide $
foldr (\ t acc -> acc >>= T.addTreeRight t)
addToOneSide :: ( ArrowList a
, NavigatableTreeToTree nt t
, NavigatableTreeModify nt t
) =>
( Maybe (nt b) -> [t b] -> Maybe (nt b) ) ->
a (t b) (t b) ->
a (nt b) (nt b)
addToOneSide side f = ( ( remNav >>> listA f )
&&&
this
)
>>>
arrL ( uncurry (\ ts nt -> side (Just nt) ts)
>>>
maybeToList
)
dropFromTheLeft :: ( ArrowList a
, NavigatableTreeModify nt t
) =>
a (nt b) (nt b)
dropFromTheLeft = arrL $ T.dropTreeLeft >>> maybeToList
dropFromTheRight :: ( ArrowList a
, NavigatableTreeModify nt t
) =>
a (nt b) (nt b)
dropFromTheRight = arrL $ T.dropTreeRight >>> maybeToList