module Data.Tree.NTree.Zipper.TypeDefs
where
import Data.Tree.Class
import Data.Tree.NavigatableTree.Class
import Data.Tree.NavigatableTree.XPathAxis ( childAxis )
import Data.Tree.NTree.TypeDefs
data NTZipper a = NTZ
{ ntree :: (NTree a)
, context :: (NTBreadCrumbs a)
}
deriving (Show)
type NTBreadCrumbs a = [NTCrumb a]
data NTCrumb a = NTC
(NTrees a)
a
(NTrees a)
deriving (Show)
toNTZipper :: NTree a -> NTZipper a
toNTZipper t = NTZ t []
fromNTZipper :: NTZipper a -> NTree a
fromNTZipper = ntree
up :: NTZipper a -> Maybe (NTZipper a)
up z
| isTop z = Nothing
| otherwise = Just $ NTZ (up1 t bc) bcs
where
NTZ t (bc : bcs) = z
down :: NTZipper a -> Maybe (NTZipper a)
down (NTZ (NTree n cs) bcs)
| null cs = Nothing
| otherwise = Just $ NTZ (head cs) (NTC [] n (tail cs) : bcs)
toTheRight :: NTZipper a -> Maybe (NTZipper a)
toTheRight z
| isTop z
||
null rs = Nothing
| otherwise = Just $ NTZ t' (bc' : bcs)
where
(NTZ t (bc : bcs)) = z
(NTC ls n rs) = bc
t' = head rs
bc' = NTC (t : ls) n (tail rs)
toTheLeft :: NTZipper a -> Maybe (NTZipper a)
toTheLeft z
| isTop z
||
null ls = Nothing
| otherwise = Just $ NTZ t' (bc' : bcs)
where
(NTZ t (bc : bcs)) = z
(NTC ls n rs) = bc
t' = head ls
bc' = NTC (tail ls) n (t : rs)
addToTheLeft :: NTree a -> NTZipper a -> Maybe (NTZipper a)
addToTheLeft t z
| isTop z = Nothing
| otherwise = Just $ NTZ t' (NTC (t:ls) n rs : bcs)
where
(NTZ t' (bc : bcs)) = z
(NTC ls n rs) = bc
addToTheRight :: NTree a -> NTZipper a -> Maybe (NTZipper a)
addToTheRight t z
| isTop z = Nothing
| otherwise = Just $ NTZ t' (NTC ls n (t:rs) : bcs)
where
(NTZ t' (bc : bcs)) = z
(NTC ls n rs) = bc
dropFromTheLeft :: NTZipper a -> Maybe (NTZipper a)
dropFromTheLeft z
| isTop z = Nothing
| null ls = Nothing
| otherwise = Just $ NTZ t' (NTC (tail ls) n rs : bcs)
where
(NTZ t' (bc : bcs)) = z
(NTC ls n rs) = bc
dropFromTheRight :: NTZipper a -> Maybe (NTZipper a)
dropFromTheRight z
| isTop z = Nothing
| null rs = Nothing
| otherwise = Just $ NTZ t' (NTC ls n (tail rs) : bcs)
where
(NTZ t' (bc : bcs)) = z
(NTC ls n rs) = bc
isTop :: NTZipper a -> Bool
isTop = null . context
up1 :: NTree a -> NTCrumb a -> NTree a
up1 t (NTC ls n rs) = NTree n (foldl (flip (:)) (t : rs) ls)
instance Functor NTZipper where
fmap f (NTZ t xs) = NTZ (fmap f t) (map (fmap f) xs)
instance Functor NTCrumb where
fmap f (NTC xs x ys)= NTC (map (fmap f) xs) (f x) (map (fmap f) ys)
instance Tree NTZipper where
mkTree n cl = toNTZipper . mkTree n $ map ntree cl
getNode = getNode . ntree
getChildren = childAxis
changeNode cf t = t { ntree = changeNode cf (ntree t) }
changeChildren cf t = t { ntree = setChildren (map ntree . cf . childAxis $ t) (ntree t) }
foldTree f = foldTree f . ntree
instance NavigatableTree NTZipper where
mvDown = down
mvUp = up
mvLeft = toTheLeft
mvRight = toTheRight
instance NavigatableTreeToTree NTZipper NTree where
fromTree = toNTZipper
toTree = fromNTZipper
instance NavigatableTreeModify NTZipper NTree where
addTreeLeft = addToTheLeft
addTreeRight = addToTheRight
dropTreeLeft = dropFromTheLeft
dropTreeRight = dropFromTheRight
substThisTree t nt = nt { ntree = t }