{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies #-}
{-# OPTIONS -fno-warn-orphans #-}
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
{ NTZipper a -> NTree a
ntree :: (NTree a)
, NTZipper a -> NTBreadCrumbs a
context :: (NTBreadCrumbs a)
}
deriving (Int -> NTZipper a -> ShowS
[NTZipper a] -> ShowS
NTZipper a -> String
(Int -> NTZipper a -> ShowS)
-> (NTZipper a -> String)
-> ([NTZipper a] -> ShowS)
-> Show (NTZipper a)
forall a. Show a => Int -> NTZipper a -> ShowS
forall a. Show a => [NTZipper a] -> ShowS
forall a. Show a => NTZipper a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NTZipper a] -> ShowS
$cshowList :: forall a. Show a => [NTZipper a] -> ShowS
show :: NTZipper a -> String
$cshow :: forall a. Show a => NTZipper a -> String
showsPrec :: Int -> NTZipper a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> NTZipper a -> ShowS
Show)
type NTBreadCrumbs a = [NTCrumb a]
data NTCrumb a = NTC
(NTrees a)
a
(NTrees a)
deriving (Int -> NTCrumb a -> ShowS
[NTCrumb a] -> ShowS
NTCrumb a -> String
(Int -> NTCrumb a -> ShowS)
-> (NTCrumb a -> String)
-> ([NTCrumb a] -> ShowS)
-> Show (NTCrumb a)
forall a. Show a => Int -> NTCrumb a -> ShowS
forall a. Show a => [NTCrumb a] -> ShowS
forall a. Show a => NTCrumb a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NTCrumb a] -> ShowS
$cshowList :: forall a. Show a => [NTCrumb a] -> ShowS
show :: NTCrumb a -> String
$cshow :: forall a. Show a => NTCrumb a -> String
showsPrec :: Int -> NTCrumb a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> NTCrumb a -> ShowS
Show)
toNTZipper :: NTree a -> NTZipper a
toNTZipper :: NTree a -> NTZipper a
toNTZipper NTree a
t = NTree a -> NTBreadCrumbs a -> NTZipper a
forall a. NTree a -> NTBreadCrumbs a -> NTZipper a
NTZ NTree a
t []
{-# INLINE toNTZipper #-}
fromNTZipper :: NTZipper a -> NTree a
fromNTZipper :: NTZipper a -> NTree a
fromNTZipper = NTZipper a -> NTree a
forall a. NTZipper a -> NTree a
ntree
{-# INLINE fromNTZipper #-}
up :: NTZipper a -> Maybe (NTZipper a)
up :: NTZipper a -> Maybe (NTZipper a)
up NTZipper a
z
| NTZipper a -> Bool
forall a. NTZipper a -> Bool
isTop NTZipper a
z = Maybe (NTZipper a)
forall a. Maybe a
Nothing
| Bool
otherwise = NTZipper a -> Maybe (NTZipper a)
forall a. a -> Maybe a
Just (NTZipper a -> Maybe (NTZipper a))
-> NTZipper a -> Maybe (NTZipper a)
forall a b. (a -> b) -> a -> b
$ NTree a -> NTBreadCrumbs a -> NTZipper a
forall a. NTree a -> NTBreadCrumbs a -> NTZipper a
NTZ (NTree a -> NTCrumb a -> NTree a
forall a. NTree a -> NTCrumb a -> NTree a
up1 NTree a
t NTCrumb a
bc) NTBreadCrumbs a
bcs
where
NTZ NTree a
t (NTCrumb a
bc : NTBreadCrumbs a
bcs) = NTZipper a
z
{-# INLINE up #-}
down :: NTZipper a -> Maybe (NTZipper a)
down :: NTZipper a -> Maybe (NTZipper a)
down (NTZ (NTree a
n NTrees a
cs) NTBreadCrumbs a
bcs)
| NTrees a -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null NTrees a
cs = Maybe (NTZipper a)
forall a. Maybe a
Nothing
| Bool
otherwise = NTZipper a -> Maybe (NTZipper a)
forall a. a -> Maybe a
Just (NTZipper a -> Maybe (NTZipper a))
-> NTZipper a -> Maybe (NTZipper a)
forall a b. (a -> b) -> a -> b
$ NTree a -> NTBreadCrumbs a -> NTZipper a
forall a. NTree a -> NTBreadCrumbs a -> NTZipper a
NTZ (NTrees a -> NTree a
forall a. [a] -> a
head NTrees a
cs) (NTrees a -> a -> NTrees a -> NTCrumb a
forall a. NTrees a -> a -> NTrees a -> NTCrumb a
NTC [] a
n (NTrees a -> NTrees a
forall a. [a] -> [a]
tail NTrees a
cs) NTCrumb a -> NTBreadCrumbs a -> NTBreadCrumbs a
forall a. a -> [a] -> [a]
: NTBreadCrumbs a
bcs)
{-# INLINE down #-}
toTheRight :: NTZipper a -> Maybe (NTZipper a)
toTheRight :: NTZipper a -> Maybe (NTZipper a)
toTheRight NTZipper a
z
| NTZipper a -> Bool
forall a. NTZipper a -> Bool
isTop NTZipper a
z
Bool -> Bool -> Bool
||
[NTree a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [NTree a]
rs = Maybe (NTZipper a)
forall a. Maybe a
Nothing
| Bool
otherwise = NTZipper a -> Maybe (NTZipper a)
forall a. a -> Maybe a
Just (NTZipper a -> Maybe (NTZipper a))
-> NTZipper a -> Maybe (NTZipper a)
forall a b. (a -> b) -> a -> b
$ NTree a -> NTBreadCrumbs a -> NTZipper a
forall a. NTree a -> NTBreadCrumbs a -> NTZipper a
NTZ NTree a
t' (NTCrumb a
bc' NTCrumb a -> NTBreadCrumbs a -> NTBreadCrumbs a
forall a. a -> [a] -> [a]
: NTBreadCrumbs a
bcs)
where
(NTZ NTree a
t (NTCrumb a
bc : NTBreadCrumbs a
bcs)) = NTZipper a
z
(NTC [NTree a]
ls a
n [NTree a]
rs) = NTCrumb a
bc
t' :: NTree a
t' = [NTree a] -> NTree a
forall a. [a] -> a
head [NTree a]
rs
bc' :: NTCrumb a
bc' = [NTree a] -> a -> [NTree a] -> NTCrumb a
forall a. NTrees a -> a -> NTrees a -> NTCrumb a
NTC (NTree a
t NTree a -> [NTree a] -> [NTree a]
forall a. a -> [a] -> [a]
: [NTree a]
ls) a
n ([NTree a] -> [NTree a]
forall a. [a] -> [a]
tail [NTree a]
rs)
{-# INLINE toTheRight #-}
toTheLeft :: NTZipper a -> Maybe (NTZipper a)
toTheLeft :: NTZipper a -> Maybe (NTZipper a)
toTheLeft NTZipper a
z
| NTZipper a -> Bool
forall a. NTZipper a -> Bool
isTop NTZipper a
z
Bool -> Bool -> Bool
||
[NTree a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [NTree a]
ls = Maybe (NTZipper a)
forall a. Maybe a
Nothing
| Bool
otherwise = NTZipper a -> Maybe (NTZipper a)
forall a. a -> Maybe a
Just (NTZipper a -> Maybe (NTZipper a))
-> NTZipper a -> Maybe (NTZipper a)
forall a b. (a -> b) -> a -> b
$ NTree a -> NTBreadCrumbs a -> NTZipper a
forall a. NTree a -> NTBreadCrumbs a -> NTZipper a
NTZ NTree a
t' (NTCrumb a
bc' NTCrumb a -> NTBreadCrumbs a -> NTBreadCrumbs a
forall a. a -> [a] -> [a]
: NTBreadCrumbs a
bcs)
where
(NTZ NTree a
t (NTCrumb a
bc : NTBreadCrumbs a
bcs)) = NTZipper a
z
(NTC [NTree a]
ls a
n [NTree a]
rs) = NTCrumb a
bc
t' :: NTree a
t' = [NTree a] -> NTree a
forall a. [a] -> a
head [NTree a]
ls
bc' :: NTCrumb a
bc' = [NTree a] -> a -> [NTree a] -> NTCrumb a
forall a. NTrees a -> a -> NTrees a -> NTCrumb a
NTC ([NTree a] -> [NTree a]
forall a. [a] -> [a]
tail [NTree a]
ls) a
n (NTree a
t NTree a -> [NTree a] -> [NTree a]
forall a. a -> [a] -> [a]
: [NTree a]
rs)
{-# INLINE toTheLeft #-}
addToTheLeft :: NTree a -> NTZipper a -> Maybe (NTZipper a)
addToTheLeft :: NTree a -> NTZipper a -> Maybe (NTZipper a)
addToTheLeft NTree a
t NTZipper a
z
| NTZipper a -> Bool
forall a. NTZipper a -> Bool
isTop NTZipper a
z = Maybe (NTZipper a)
forall a. Maybe a
Nothing
| Bool
otherwise = NTZipper a -> Maybe (NTZipper a)
forall a. a -> Maybe a
Just (NTZipper a -> Maybe (NTZipper a))
-> NTZipper a -> Maybe (NTZipper a)
forall a b. (a -> b) -> a -> b
$ NTree a -> NTBreadCrumbs a -> NTZipper a
forall a. NTree a -> NTBreadCrumbs a -> NTZipper a
NTZ NTree a
t' (NTrees a -> a -> NTrees a -> NTCrumb a
forall a. NTrees a -> a -> NTrees a -> NTCrumb a
NTC (NTree a
tNTree a -> NTrees a -> NTrees a
forall a. a -> [a] -> [a]
:NTrees a
ls) a
n NTrees a
rs NTCrumb a -> NTBreadCrumbs a -> NTBreadCrumbs a
forall a. a -> [a] -> [a]
: NTBreadCrumbs a
bcs)
where
(NTZ NTree a
t' (NTCrumb a
bc : NTBreadCrumbs a
bcs)) = NTZipper a
z
(NTC NTrees a
ls a
n NTrees a
rs) = NTCrumb a
bc
{-# INLINE addToTheLeft #-}
addToTheRight :: NTree a -> NTZipper a -> Maybe (NTZipper a)
addToTheRight :: NTree a -> NTZipper a -> Maybe (NTZipper a)
addToTheRight NTree a
t NTZipper a
z
| NTZipper a -> Bool
forall a. NTZipper a -> Bool
isTop NTZipper a
z = Maybe (NTZipper a)
forall a. Maybe a
Nothing
| Bool
otherwise = NTZipper a -> Maybe (NTZipper a)
forall a. a -> Maybe a
Just (NTZipper a -> Maybe (NTZipper a))
-> NTZipper a -> Maybe (NTZipper a)
forall a b. (a -> b) -> a -> b
$ NTree a -> NTBreadCrumbs a -> NTZipper a
forall a. NTree a -> NTBreadCrumbs a -> NTZipper a
NTZ NTree a
t' (NTrees a -> a -> NTrees a -> NTCrumb a
forall a. NTrees a -> a -> NTrees a -> NTCrumb a
NTC NTrees a
ls a
n (NTree a
tNTree a -> NTrees a -> NTrees a
forall a. a -> [a] -> [a]
:NTrees a
rs) NTCrumb a -> NTBreadCrumbs a -> NTBreadCrumbs a
forall a. a -> [a] -> [a]
: NTBreadCrumbs a
bcs)
where
(NTZ NTree a
t' (NTCrumb a
bc : NTBreadCrumbs a
bcs)) = NTZipper a
z
(NTC NTrees a
ls a
n NTrees a
rs) = NTCrumb a
bc
{-# INLINE addToTheRight #-}
dropFromTheLeft :: NTZipper a -> Maybe (NTZipper a)
dropFromTheLeft :: NTZipper a -> Maybe (NTZipper a)
dropFromTheLeft NTZipper a
z
| NTZipper a -> Bool
forall a. NTZipper a -> Bool
isTop NTZipper a
z = Maybe (NTZipper a)
forall a. Maybe a
Nothing
| [NTree a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [NTree a]
ls = Maybe (NTZipper a)
forall a. Maybe a
Nothing
| Bool
otherwise = NTZipper a -> Maybe (NTZipper a)
forall a. a -> Maybe a
Just (NTZipper a -> Maybe (NTZipper a))
-> NTZipper a -> Maybe (NTZipper a)
forall a b. (a -> b) -> a -> b
$ NTree a -> NTBreadCrumbs a -> NTZipper a
forall a. NTree a -> NTBreadCrumbs a -> NTZipper a
NTZ NTree a
t' ([NTree a] -> a -> [NTree a] -> NTCrumb a
forall a. NTrees a -> a -> NTrees a -> NTCrumb a
NTC ([NTree a] -> [NTree a]
forall a. [a] -> [a]
tail [NTree a]
ls) a
n [NTree a]
rs NTCrumb a -> NTBreadCrumbs a -> NTBreadCrumbs a
forall a. a -> [a] -> [a]
: NTBreadCrumbs a
bcs)
where
(NTZ NTree a
t' (NTCrumb a
bc : NTBreadCrumbs a
bcs)) = NTZipper a
z
(NTC [NTree a]
ls a
n [NTree a]
rs) = NTCrumb a
bc
{-# INLINE dropFromTheLeft #-}
dropFromTheRight :: NTZipper a -> Maybe (NTZipper a)
dropFromTheRight :: NTZipper a -> Maybe (NTZipper a)
dropFromTheRight NTZipper a
z
| NTZipper a -> Bool
forall a. NTZipper a -> Bool
isTop NTZipper a
z = Maybe (NTZipper a)
forall a. Maybe a
Nothing
| [NTree a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [NTree a]
rs = Maybe (NTZipper a)
forall a. Maybe a
Nothing
| Bool
otherwise = NTZipper a -> Maybe (NTZipper a)
forall a. a -> Maybe a
Just (NTZipper a -> Maybe (NTZipper a))
-> NTZipper a -> Maybe (NTZipper a)
forall a b. (a -> b) -> a -> b
$ NTree a -> NTBreadCrumbs a -> NTZipper a
forall a. NTree a -> NTBreadCrumbs a -> NTZipper a
NTZ NTree a
t' ([NTree a] -> a -> [NTree a] -> NTCrumb a
forall a. NTrees a -> a -> NTrees a -> NTCrumb a
NTC [NTree a]
ls a
n ([NTree a] -> [NTree a]
forall a. [a] -> [a]
tail [NTree a]
rs) NTCrumb a -> NTBreadCrumbs a -> NTBreadCrumbs a
forall a. a -> [a] -> [a]
: NTBreadCrumbs a
bcs)
where
(NTZ NTree a
t' (NTCrumb a
bc : NTBreadCrumbs a
bcs)) = NTZipper a
z
(NTC [NTree a]
ls a
n [NTree a]
rs) = NTCrumb a
bc
{-# INLINE dropFromTheRight #-}
isTop :: NTZipper a -> Bool
isTop :: NTZipper a -> Bool
isTop = [NTCrumb a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null ([NTCrumb a] -> Bool)
-> (NTZipper a -> [NTCrumb a]) -> NTZipper a -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NTZipper a -> [NTCrumb a]
forall a. NTZipper a -> NTBreadCrumbs a
context
{-# INLINE isTop #-}
up1 :: NTree a -> NTCrumb a -> NTree a
up1 :: NTree a -> NTCrumb a -> NTree a
up1 NTree a
t (NTC NTrees a
ls a
n NTrees a
rs) = a -> NTrees a -> NTree a
forall a. a -> NTrees a -> NTree a
NTree a
n ((NTrees a -> NTree a -> NTrees a)
-> NTrees a -> NTrees a -> NTrees a
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl ((NTree a -> NTrees a -> NTrees a)
-> NTrees a -> NTree a -> NTrees a
forall a b c. (a -> b -> c) -> b -> a -> c
flip (:)) (NTree a
t NTree a -> NTrees a -> NTrees a
forall a. a -> [a] -> [a]
: NTrees a
rs) NTrees a
ls)
{-# INLINE up1 #-}
instance Functor NTZipper where
fmap :: (a -> b) -> NTZipper a -> NTZipper b
fmap a -> b
f (NTZ NTree a
t NTBreadCrumbs a
xs) = NTree b -> NTBreadCrumbs b -> NTZipper b
forall a. NTree a -> NTBreadCrumbs a -> NTZipper a
NTZ ((a -> b) -> NTree a -> NTree b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f NTree a
t) ((NTCrumb a -> NTCrumb b) -> NTBreadCrumbs a -> NTBreadCrumbs b
forall a b. (a -> b) -> [a] -> [b]
map ((a -> b) -> NTCrumb a -> NTCrumb b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f) NTBreadCrumbs a
xs)
{-# INLINE fmap #-}
instance Functor NTCrumb where
fmap :: (a -> b) -> NTCrumb a -> NTCrumb b
fmap a -> b
f (NTC NTrees a
xs a
x NTrees a
ys)= NTrees b -> b -> NTrees b -> NTCrumb b
forall a. NTrees a -> a -> NTrees a -> NTCrumb a
NTC ((NTree a -> NTree b) -> NTrees a -> NTrees b
forall a b. (a -> b) -> [a] -> [b]
map ((a -> b) -> NTree a -> NTree b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f) NTrees a
xs) (a -> b
f a
x) ((NTree a -> NTree b) -> NTrees a -> NTrees b
forall a b. (a -> b) -> [a] -> [b]
map ((a -> b) -> NTree a -> NTree b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f) NTrees a
ys)
{-# INLINE fmap #-}
instance Tree NTZipper where
mkTree :: a -> [NTZipper a] -> NTZipper a
mkTree a
n [NTZipper a]
cl = NTree a -> NTZipper a
forall a. NTree a -> NTZipper a
toNTZipper (NTree a -> NTZipper a)
-> ([NTree a] -> NTree a) -> [NTree a] -> NTZipper a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> [NTree a] -> NTree a
forall (t :: * -> *) a. Tree t => a -> [t a] -> t a
mkTree a
n ([NTree a] -> NTZipper a) -> [NTree a] -> NTZipper a
forall a b. (a -> b) -> a -> b
$ (NTZipper a -> NTree a) -> [NTZipper a] -> [NTree a]
forall a b. (a -> b) -> [a] -> [b]
map NTZipper a -> NTree a
forall a. NTZipper a -> NTree a
ntree [NTZipper a]
cl
getNode :: NTZipper a -> a
getNode = NTree a -> a
forall (t :: * -> *) a. Tree t => t a -> a
getNode (NTree a -> a) -> (NTZipper a -> NTree a) -> NTZipper a -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NTZipper a -> NTree a
forall a. NTZipper a -> NTree a
ntree
{-# INLINE getNode #-}
getChildren :: NTZipper a -> [NTZipper a]
getChildren = NTZipper a -> [NTZipper a]
forall (t :: * -> *) a. NavigatableTree t => t a -> [t a]
childAxis
{-# INLINE getChildren #-}
changeNode :: (a -> a) -> NTZipper a -> NTZipper a
changeNode a -> a
cf NTZipper a
t = NTZipper a
t { ntree :: NTree a
ntree = (a -> a) -> NTree a -> NTree a
forall (t :: * -> *) a. Tree t => (a -> a) -> t a -> t a
changeNode a -> a
cf (NTZipper a -> NTree a
forall a. NTZipper a -> NTree a
ntree NTZipper a
t) }
changeChildren :: ([NTZipper a] -> [NTZipper a]) -> NTZipper a -> NTZipper a
changeChildren [NTZipper a] -> [NTZipper a]
cf NTZipper a
t = NTZipper a
t { ntree :: NTree a
ntree = [NTree a] -> NTree a -> NTree a
forall (t :: * -> *) a. Tree t => [t a] -> t a -> t a
setChildren ((NTZipper a -> NTree a) -> [NTZipper a] -> [NTree a]
forall a b. (a -> b) -> [a] -> [b]
map NTZipper a -> NTree a
forall a. NTZipper a -> NTree a
ntree ([NTZipper a] -> [NTree a])
-> (NTZipper a -> [NTZipper a]) -> NTZipper a -> [NTree a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [NTZipper a] -> [NTZipper a]
cf ([NTZipper a] -> [NTZipper a])
-> (NTZipper a -> [NTZipper a]) -> NTZipper a -> [NTZipper a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NTZipper a -> [NTZipper a]
forall (t :: * -> *) a. NavigatableTree t => t a -> [t a]
childAxis (NTZipper a -> [NTree a]) -> NTZipper a -> [NTree a]
forall a b. (a -> b) -> a -> b
$ NTZipper a
t) (NTZipper a -> NTree a
forall a. NTZipper a -> NTree a
ntree NTZipper a
t) }
foldTree :: (a -> [b] -> b) -> NTZipper a -> b
foldTree a -> [b] -> b
f = (a -> [b] -> b) -> NTree a -> b
forall (t :: * -> *) a b. Tree t => (a -> [b] -> b) -> t a -> b
foldTree a -> [b] -> b
f (NTree a -> b) -> (NTZipper a -> NTree a) -> NTZipper a -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NTZipper a -> NTree a
forall a. NTZipper a -> NTree a
ntree
{-# INLINE foldTree #-}
instance NavigatableTree NTZipper where
mvDown :: NTZipper a -> Maybe (NTZipper a)
mvDown = NTZipper a -> Maybe (NTZipper a)
forall a. NTZipper a -> Maybe (NTZipper a)
down
{-# INLINE mvDown #-}
mvUp :: NTZipper a -> Maybe (NTZipper a)
mvUp = NTZipper a -> Maybe (NTZipper a)
forall a. NTZipper a -> Maybe (NTZipper a)
up
{-# INLINE mvUp #-}
mvLeft :: NTZipper a -> Maybe (NTZipper a)
mvLeft = NTZipper a -> Maybe (NTZipper a)
forall a. NTZipper a -> Maybe (NTZipper a)
toTheLeft
{-# INLINE mvLeft #-}
mvRight :: NTZipper a -> Maybe (NTZipper a)
mvRight = NTZipper a -> Maybe (NTZipper a)
forall a. NTZipper a -> Maybe (NTZipper a)
toTheRight
{-# INLINE mvRight #-}
instance NavigatableTreeToTree NTZipper NTree where
fromTree :: NTree a -> NTZipper a
fromTree = NTree a -> NTZipper a
forall a. NTree a -> NTZipper a
toNTZipper
{-# INLINE fromTree #-}
toTree :: NTZipper a -> NTree a
toTree = NTZipper a -> NTree a
forall a. NTZipper a -> NTree a
fromNTZipper
{-# INLINE toTree #-}
instance NavigatableTreeModify NTZipper NTree where
addTreeLeft :: NTree a -> NTZipper a -> Maybe (NTZipper a)
addTreeLeft = NTree a -> NTZipper a -> Maybe (NTZipper a)
forall a. NTree a -> NTZipper a -> Maybe (NTZipper a)
addToTheLeft
{-# INLINE addTreeLeft #-}
addTreeRight :: NTree a -> NTZipper a -> Maybe (NTZipper a)
addTreeRight = NTree a -> NTZipper a -> Maybe (NTZipper a)
forall a. NTree a -> NTZipper a -> Maybe (NTZipper a)
addToTheRight
{-# INLINE addTreeRight #-}
dropTreeLeft :: NTZipper a -> Maybe (NTZipper a)
dropTreeLeft = NTZipper a -> Maybe (NTZipper a)
forall a. NTZipper a -> Maybe (NTZipper a)
dropFromTheLeft
{-# INLINE dropTreeLeft #-}
dropTreeRight :: NTZipper a -> Maybe (NTZipper a)
dropTreeRight = NTZipper a -> Maybe (NTZipper a)
forall a. NTZipper a -> Maybe (NTZipper a)
dropFromTheRight
{-# INLINE dropTreeRight #-}
substThisTree :: NTree a -> NTZipper a -> NTZipper a
substThisTree NTree a
t NTZipper a
nt = NTZipper a
nt { ntree :: NTree a
ntree = NTree a
t }
{-# INLINE substThisTree #-}