{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TypeFamilies #-}
module Cursor.Tree.Insert
( treeCursorInsert,
treeCursorInsertAndSelect,
treeCursorInsertNodeSingleAndSelect,
treeCursorInsertNodeAndSelect,
treeCursorAppend,
treeCursorAppendAndSelect,
treeCursorAppendNodeSingleAndSelect,
treeCursorAppendNodeAndSelect,
treeCursorAddChildAtPos,
treeCursorAddChildAtStart,
treeCursorAddChildAtEnd,
treeCursorAddChildAtPosAndSelect,
treeCursorAddChildAtStartAndSelect,
treeCursorAddChildAtEndAndSelect,
treeCursorAddChildNodeSingleAtPosAndSelect,
treeCursorAddChildNodeSingleAtStartAndSelect,
treeCursorAddChildNodeSingleAtEndAndSelect,
treeCursorAddChildNodeAtPosAndSelect,
treeCursorAddChildNodeAtStartAndSelect,
treeCursorAddChildNodeAtEndAndSelect,
)
where
import Cursor.Tree.Types
import Data.List.NonEmpty ((<|))
import qualified Data.List.NonEmpty as NE
import Data.Tree
treeCursorInsert :: Tree b -> TreeCursor a b -> Maybe (TreeCursor a b)
treeCursorInsert :: Tree b -> TreeCursor a b -> Maybe (TreeCursor a b)
treeCursorInsert Tree b
tree tc :: TreeCursor a b
tc@TreeCursor {a
Maybe (TreeAbove b)
CForest b
treeBelow :: forall a b. TreeCursor a b -> CForest b
treeCurrent :: forall a b. TreeCursor a b -> a
treeAbove :: forall a b. TreeCursor a b -> Maybe (TreeAbove b)
treeBelow :: CForest b
treeCurrent :: a
treeAbove :: Maybe (TreeAbove b)
..} = do
TreeAbove b
ta <- Maybe (TreeAbove b)
treeAbove
let newTreeAbove :: TreeAbove b
newTreeAbove = TreeAbove b
ta {treeAboveLefts :: [CTree b]
treeAboveLefts = Tree b -> CTree b
forall a. Tree a -> CTree a
makeCTree Tree b
tree CTree b -> [CTree b] -> [CTree b]
forall a. a -> [a] -> [a]
: TreeAbove b -> [CTree b]
forall b. TreeAbove b -> [CTree b]
treeAboveLefts TreeAbove b
ta}
TreeCursor a b -> Maybe (TreeCursor a b)
forall (f :: * -> *) a. Applicative f => a -> f a
pure TreeCursor a b
tc {treeAbove :: Maybe (TreeAbove b)
treeAbove = TreeAbove b -> Maybe (TreeAbove b)
forall a. a -> Maybe a
Just TreeAbove b
newTreeAbove}
treeCursorInsertAndSelect ::
(a -> b) -> (b -> a) -> Tree b -> TreeCursor a b -> Maybe (TreeCursor a b)
treeCursorInsertAndSelect :: (a -> b)
-> (b -> a) -> Tree b -> TreeCursor a b -> Maybe (TreeCursor a b)
treeCursorInsertAndSelect a -> b
f b -> a
g (Node b
value Forest b
forest) = (a -> b)
-> a -> CForest b -> TreeCursor a b -> Maybe (TreeCursor a b)
forall a b.
(a -> b)
-> a -> CForest b -> TreeCursor a b -> Maybe (TreeCursor a b)
treeCursorInsertNodeAndSelect a -> b
f (b -> a
g b
value) (Forest b -> CForest b
forall a. Forest a -> CForest a
makeCForest Forest b
forest)
treeCursorInsertNodeSingleAndSelect ::
(a -> b) -> a -> TreeCursor a b -> Maybe (TreeCursor a b)
treeCursorInsertNodeSingleAndSelect :: (a -> b) -> a -> TreeCursor a b -> Maybe (TreeCursor a b)
treeCursorInsertNodeSingleAndSelect a -> b
f a
a = (a -> b)
-> a -> CForest b -> TreeCursor a b -> Maybe (TreeCursor a b)
forall a b.
(a -> b)
-> a -> CForest b -> TreeCursor a b -> Maybe (TreeCursor a b)
treeCursorInsertNodeAndSelect a -> b
f a
a CForest b
forall a. CForest a
EmptyCForest
treeCursorInsertNodeAndSelect ::
(a -> b) -> a -> CForest b -> TreeCursor a b -> Maybe (TreeCursor a b)
treeCursorInsertNodeAndSelect :: (a -> b)
-> a -> CForest b -> TreeCursor a b -> Maybe (TreeCursor a b)
treeCursorInsertNodeAndSelect a -> b
f a
value CForest b
forest TreeCursor a b
tc = do
TreeAbove b
ta <- TreeCursor a b -> Maybe (TreeAbove b)
forall a b. TreeCursor a b -> Maybe (TreeAbove b)
treeAbove TreeCursor a b
tc
let ta' :: TreeAbove b
ta' = TreeAbove b
ta {treeAboveRights :: [CTree b]
treeAboveRights = b -> CForest b -> CTree b
forall a. a -> CForest a -> CTree a
CNode (a -> b
f (TreeCursor a b -> a
forall a b. TreeCursor a b -> a
treeCurrent TreeCursor a b
tc)) (TreeCursor a b -> CForest b
forall a b. TreeCursor a b -> CForest b
treeBelow TreeCursor a b
tc) CTree b -> [CTree b] -> [CTree b]
forall a. a -> [a] -> [a]
: TreeAbove b -> [CTree b]
forall b. TreeAbove b -> [CTree b]
treeAboveRights TreeAbove b
ta}
tc' :: TreeCursor a b
tc' = TreeCursor a b
tc {treeAbove :: Maybe (TreeAbove b)
treeAbove = TreeAbove b -> Maybe (TreeAbove b)
forall a. a -> Maybe a
Just TreeAbove b
ta', treeCurrent :: a
treeCurrent = a
value, treeBelow :: CForest b
treeBelow = CForest b
forest}
TreeCursor a b -> Maybe (TreeCursor a b)
forall (f :: * -> *) a. Applicative f => a -> f a
pure TreeCursor a b
tc'
treeCursorAppend :: Tree b -> TreeCursor a b -> Maybe (TreeCursor a b)
treeCursorAppend :: Tree b -> TreeCursor a b -> Maybe (TreeCursor a b)
treeCursorAppend Tree b
tree tc :: TreeCursor a b
tc@TreeCursor {a
Maybe (TreeAbove b)
CForest b
treeBelow :: CForest b
treeCurrent :: a
treeAbove :: Maybe (TreeAbove b)
treeBelow :: forall a b. TreeCursor a b -> CForest b
treeCurrent :: forall a b. TreeCursor a b -> a
treeAbove :: forall a b. TreeCursor a b -> Maybe (TreeAbove b)
..} = do
TreeAbove b
ta <- Maybe (TreeAbove b)
treeAbove
let newTreeAbove :: TreeAbove b
newTreeAbove = TreeAbove b
ta {treeAboveRights :: [CTree b]
treeAboveRights = Tree b -> CTree b
forall a. Tree a -> CTree a
makeCTree Tree b
tree CTree b -> [CTree b] -> [CTree b]
forall a. a -> [a] -> [a]
: TreeAbove b -> [CTree b]
forall b. TreeAbove b -> [CTree b]
treeAboveRights TreeAbove b
ta}
TreeCursor a b -> Maybe (TreeCursor a b)
forall (f :: * -> *) a. Applicative f => a -> f a
pure TreeCursor a b
tc {treeAbove :: Maybe (TreeAbove b)
treeAbove = TreeAbove b -> Maybe (TreeAbove b)
forall a. a -> Maybe a
Just TreeAbove b
newTreeAbove}
treeCursorAppendAndSelect ::
(a -> b) -> (b -> a) -> Tree b -> TreeCursor a b -> Maybe (TreeCursor a b)
treeCursorAppendAndSelect :: (a -> b)
-> (b -> a) -> Tree b -> TreeCursor a b -> Maybe (TreeCursor a b)
treeCursorAppendAndSelect a -> b
f b -> a
g (Node b
value Forest b
forest) = (a -> b)
-> a -> CForest b -> TreeCursor a b -> Maybe (TreeCursor a b)
forall a b.
(a -> b)
-> a -> CForest b -> TreeCursor a b -> Maybe (TreeCursor a b)
treeCursorAppendNodeAndSelect a -> b
f (b -> a
g b
value) (Forest b -> CForest b
forall a. Forest a -> CForest a
makeCForest Forest b
forest)
treeCursorAppendNodeSingleAndSelect ::
(a -> b) -> a -> TreeCursor a b -> Maybe (TreeCursor a b)
treeCursorAppendNodeSingleAndSelect :: (a -> b) -> a -> TreeCursor a b -> Maybe (TreeCursor a b)
treeCursorAppendNodeSingleAndSelect a -> b
f a
a = (a -> b)
-> a -> CForest b -> TreeCursor a b -> Maybe (TreeCursor a b)
forall a b.
(a -> b)
-> a -> CForest b -> TreeCursor a b -> Maybe (TreeCursor a b)
treeCursorAppendNodeAndSelect a -> b
f a
a CForest b
forall a. CForest a
EmptyCForest
treeCursorAppendNodeAndSelect ::
(a -> b) -> a -> CForest b -> TreeCursor a b -> Maybe (TreeCursor a b)
treeCursorAppendNodeAndSelect :: (a -> b)
-> a -> CForest b -> TreeCursor a b -> Maybe (TreeCursor a b)
treeCursorAppendNodeAndSelect a -> b
f a
value CForest b
forest TreeCursor a b
tc = do
TreeAbove b
ta <- TreeCursor a b -> Maybe (TreeAbove b)
forall a b. TreeCursor a b -> Maybe (TreeAbove b)
treeAbove TreeCursor a b
tc
let ta' :: TreeAbove b
ta' = TreeAbove b
ta {treeAboveLefts :: [CTree b]
treeAboveLefts = b -> CForest b -> CTree b
forall a. a -> CForest a -> CTree a
CNode (a -> b
f (TreeCursor a b -> a
forall a b. TreeCursor a b -> a
treeCurrent TreeCursor a b
tc)) (TreeCursor a b -> CForest b
forall a b. TreeCursor a b -> CForest b
treeBelow TreeCursor a b
tc) CTree b -> [CTree b] -> [CTree b]
forall a. a -> [a] -> [a]
: TreeAbove b -> [CTree b]
forall b. TreeAbove b -> [CTree b]
treeAboveLefts TreeAbove b
ta}
tc' :: TreeCursor a b
tc' = TreeCursor a b
tc {treeAbove :: Maybe (TreeAbove b)
treeAbove = TreeAbove b -> Maybe (TreeAbove b)
forall a. a -> Maybe a
Just TreeAbove b
ta', treeCurrent :: a
treeCurrent = a
value, treeBelow :: CForest b
treeBelow = CForest b
forest}
TreeCursor a b -> Maybe (TreeCursor a b)
forall (f :: * -> *) a. Applicative f => a -> f a
pure TreeCursor a b
tc'
treeCursorAddChildAtPos :: Int -> Tree b -> TreeCursor a b -> TreeCursor a b
treeCursorAddChildAtPos :: Int -> Tree b -> TreeCursor a b -> TreeCursor a b
treeCursorAddChildAtPos Int
i Tree b
t TreeCursor a b
tc =
case TreeCursor a b -> CForest b
forall a b. TreeCursor a b -> CForest b
treeBelow TreeCursor a b
tc of
CForest b
EmptyCForest -> TreeCursor a b
tc {treeBelow :: CForest b
treeBelow = [CTree b] -> CForest b
forall a. [CTree a] -> CForest a
openForest [Tree b -> CTree b
forall a. Tree a -> CTree a
makeCTree Tree b
t]}
ClosedForest NonEmpty (Tree b)
ts ->
let ([Tree b]
before, [Tree b]
after) = Int -> [Tree b] -> ([Tree b], [Tree b])
forall a. Int -> [a] -> ([a], [a])
splitAt Int
i ([Tree b] -> ([Tree b], [Tree b]))
-> [Tree b] -> ([Tree b], [Tree b])
forall a b. (a -> b) -> a -> b
$ NonEmpty (Tree b) -> [Tree b]
forall a. NonEmpty a -> [a]
NE.toList NonEmpty (Tree b)
ts
in TreeCursor a b
tc {treeBelow :: CForest b
treeBelow = [CTree b] -> CForest b
forall a. [CTree a] -> CForest a
openForest ([CTree b] -> CForest b) -> [CTree b] -> CForest b
forall a b. (a -> b) -> a -> b
$ (Tree b -> CTree b) -> [Tree b] -> [CTree b]
forall a b. (a -> b) -> [a] -> [b]
map Tree b -> CTree b
forall a. Tree a -> CTree a
makeCTree ([Tree b] -> [CTree b]) -> [Tree b] -> [CTree b]
forall a b. (a -> b) -> a -> b
$ [Tree b]
before [Tree b] -> [Tree b] -> [Tree b]
forall a. [a] -> [a] -> [a]
++ [Tree b
t] [Tree b] -> [Tree b] -> [Tree b]
forall a. [a] -> [a] -> [a]
++ [Tree b]
after}
OpenForest NonEmpty (CTree b)
ts ->
let ([CTree b]
before, [CTree b]
after) = Int -> [CTree b] -> ([CTree b], [CTree b])
forall a. Int -> [a] -> ([a], [a])
splitAt Int
i ([CTree b] -> ([CTree b], [CTree b]))
-> [CTree b] -> ([CTree b], [CTree b])
forall a b. (a -> b) -> a -> b
$ NonEmpty (CTree b) -> [CTree b]
forall a. NonEmpty a -> [a]
NE.toList NonEmpty (CTree b)
ts
in TreeCursor a b
tc {treeBelow :: CForest b
treeBelow = [CTree b] -> CForest b
forall a. [CTree a] -> CForest a
openForest ([CTree b] -> CForest b) -> [CTree b] -> CForest b
forall a b. (a -> b) -> a -> b
$ [CTree b]
before [CTree b] -> [CTree b] -> [CTree b]
forall a. [a] -> [a] -> [a]
++ [Tree b -> CTree b
forall a. Tree a -> CTree a
makeCTree Tree b
t] [CTree b] -> [CTree b] -> [CTree b]
forall a. [a] -> [a] -> [a]
++ [CTree b]
after}
treeCursorAddChildAtStart :: Tree b -> TreeCursor a b -> TreeCursor a b
treeCursorAddChildAtStart :: Tree b -> TreeCursor a b -> TreeCursor a b
treeCursorAddChildAtStart Tree b
t TreeCursor a b
tc =
case TreeCursor a b -> CForest b
forall a b. TreeCursor a b -> CForest b
treeBelow TreeCursor a b
tc of
CForest b
EmptyCForest -> TreeCursor a b
tc {treeBelow :: CForest b
treeBelow = [CTree b] -> CForest b
forall a. [CTree a] -> CForest a
openForest [Tree b -> CTree b
forall a. Tree a -> CTree a
makeCTree Tree b
t]}
ClosedForest NonEmpty (Tree b)
ts -> TreeCursor a b
tc {treeBelow :: CForest b
treeBelow = NonEmpty (CTree b) -> CForest b
forall a. NonEmpty (CTree a) -> CForest a
OpenForest (NonEmpty (CTree b) -> CForest b)
-> NonEmpty (CTree b) -> CForest b
forall a b. (a -> b) -> a -> b
$ (Tree b -> CTree b) -> NonEmpty (Tree b) -> NonEmpty (CTree b)
forall a b. (a -> b) -> NonEmpty a -> NonEmpty b
NE.map Tree b -> CTree b
forall a. Tree a -> CTree a
makeCTree (NonEmpty (Tree b) -> NonEmpty (CTree b))
-> NonEmpty (Tree b) -> NonEmpty (CTree b)
forall a b. (a -> b) -> a -> b
$ Tree b
t Tree b -> NonEmpty (Tree b) -> NonEmpty (Tree b)
forall a. a -> NonEmpty a -> NonEmpty a
<| NonEmpty (Tree b)
ts}
OpenForest NonEmpty (CTree b)
ts -> TreeCursor a b
tc {treeBelow :: CForest b
treeBelow = NonEmpty (CTree b) -> CForest b
forall a. NonEmpty (CTree a) -> CForest a
OpenForest (NonEmpty (CTree b) -> CForest b)
-> NonEmpty (CTree b) -> CForest b
forall a b. (a -> b) -> a -> b
$ Tree b -> CTree b
forall a. Tree a -> CTree a
makeCTree Tree b
t CTree b -> NonEmpty (CTree b) -> NonEmpty (CTree b)
forall a. a -> NonEmpty a -> NonEmpty a
<| NonEmpty (CTree b)
ts}
treeCursorAddChildAtEnd :: Tree b -> TreeCursor a b -> TreeCursor a b
treeCursorAddChildAtEnd :: Tree b -> TreeCursor a b -> TreeCursor a b
treeCursorAddChildAtEnd Tree b
t TreeCursor a b
tc =
case TreeCursor a b -> CForest b
forall a b. TreeCursor a b -> CForest b
treeBelow TreeCursor a b
tc of
CForest b
EmptyCForest -> TreeCursor a b
tc {treeBelow :: CForest b
treeBelow = [CTree b] -> CForest b
forall a. [CTree a] -> CForest a
openForest [Tree b -> CTree b
forall a. Tree a -> CTree a
makeCTree Tree b
t]}
ClosedForest NonEmpty (Tree b)
ts -> TreeCursor a b
tc {treeBelow :: CForest b
treeBelow = [CTree b] -> CForest b
forall a. [CTree a] -> CForest a
openForest ([CTree b] -> CForest b) -> [CTree b] -> CForest b
forall a b. (a -> b) -> a -> b
$ (Tree b -> CTree b) -> [Tree b] -> [CTree b]
forall a b. (a -> b) -> [a] -> [b]
map Tree b -> CTree b
forall a. Tree a -> CTree a
makeCTree ([Tree b] -> [CTree b]) -> [Tree b] -> [CTree b]
forall a b. (a -> b) -> a -> b
$ NonEmpty (Tree b) -> [Tree b]
forall a. NonEmpty a -> [a]
NE.toList NonEmpty (Tree b)
ts [Tree b] -> [Tree b] -> [Tree b]
forall a. [a] -> [a] -> [a]
++ [Tree b
t]}
OpenForest NonEmpty (CTree b)
ts -> TreeCursor a b
tc {treeBelow :: CForest b
treeBelow = [CTree b] -> CForest b
forall a. [CTree a] -> CForest a
openForest ([CTree b] -> CForest b) -> [CTree b] -> CForest b
forall a b. (a -> b) -> a -> b
$ NonEmpty (CTree b) -> [CTree b]
forall a. NonEmpty a -> [a]
NE.toList NonEmpty (CTree b)
ts [CTree b] -> [CTree b] -> [CTree b]
forall a. [a] -> [a] -> [a]
++ [Tree b -> CTree b
forall a. Tree a -> CTree a
makeCTree Tree b
t]}
treeCursorAddChildAtPosAndSelect ::
(a -> b) -> (b -> a) -> Int -> Tree b -> TreeCursor a b -> TreeCursor a b
treeCursorAddChildAtPosAndSelect :: (a -> b)
-> (b -> a) -> Int -> Tree b -> TreeCursor a b -> TreeCursor a b
treeCursorAddChildAtPosAndSelect a -> b
f b -> a
g Int
i (Node b
t Forest b
ts) = (a -> b)
-> Int -> a -> Forest b -> TreeCursor a b -> TreeCursor a b
forall a b.
(a -> b)
-> Int -> a -> Forest b -> TreeCursor a b -> TreeCursor a b
treeCursorAddChildNodeAtPosAndSelect a -> b
f Int
i (b -> a
g b
t) Forest b
ts
treeCursorAddChildAtStartAndSelect ::
(a -> b) -> (b -> a) -> Tree b -> TreeCursor a b -> TreeCursor a b
treeCursorAddChildAtStartAndSelect :: (a -> b) -> (b -> a) -> Tree b -> TreeCursor a b -> TreeCursor a b
treeCursorAddChildAtStartAndSelect a -> b
f b -> a
g (Node b
t Forest b
ts) = (a -> b) -> a -> Forest b -> TreeCursor a b -> TreeCursor a b
forall a b.
(a -> b) -> a -> Forest b -> TreeCursor a b -> TreeCursor a b
treeCursorAddChildNodeAtStartAndSelect a -> b
f (b -> a
g b
t) Forest b
ts
treeCursorAddChildAtEndAndSelect ::
(a -> b) -> (b -> a) -> Tree b -> TreeCursor a b -> TreeCursor a b
treeCursorAddChildAtEndAndSelect :: (a -> b) -> (b -> a) -> Tree b -> TreeCursor a b -> TreeCursor a b
treeCursorAddChildAtEndAndSelect a -> b
f b -> a
g (Node b
t Forest b
ts) = (a -> b) -> a -> Forest b -> TreeCursor a b -> TreeCursor a b
forall a b.
(a -> b) -> a -> Forest b -> TreeCursor a b -> TreeCursor a b
treeCursorAddChildNodeAtEndAndSelect a -> b
f (b -> a
g b
t) Forest b
ts
treeCursorAddChildNodeSingleAtPosAndSelect ::
(a -> b) -> Int -> a -> TreeCursor a b -> TreeCursor a b
treeCursorAddChildNodeSingleAtPosAndSelect :: (a -> b) -> Int -> a -> TreeCursor a b -> TreeCursor a b
treeCursorAddChildNodeSingleAtPosAndSelect a -> b
f Int
i a
a = (a -> b)
-> Int -> a -> Forest b -> TreeCursor a b -> TreeCursor a b
forall a b.
(a -> b)
-> Int -> a -> Forest b -> TreeCursor a b -> TreeCursor a b
treeCursorAddChildNodeAtPosAndSelect a -> b
f Int
i a
a []
treeCursorAddChildNodeSingleAtStartAndSelect ::
(a -> b) -> a -> TreeCursor a b -> TreeCursor a b
treeCursorAddChildNodeSingleAtStartAndSelect :: (a -> b) -> a -> TreeCursor a b -> TreeCursor a b
treeCursorAddChildNodeSingleAtStartAndSelect a -> b
f a
a = (a -> b) -> a -> Forest b -> TreeCursor a b -> TreeCursor a b
forall a b.
(a -> b) -> a -> Forest b -> TreeCursor a b -> TreeCursor a b
treeCursorAddChildNodeAtStartAndSelect a -> b
f a
a []
treeCursorAddChildNodeSingleAtEndAndSelect ::
(a -> b) -> a -> TreeCursor a b -> TreeCursor a b
treeCursorAddChildNodeSingleAtEndAndSelect :: (a -> b) -> a -> TreeCursor a b -> TreeCursor a b
treeCursorAddChildNodeSingleAtEndAndSelect a -> b
f a
a = (a -> b) -> a -> Forest b -> TreeCursor a b -> TreeCursor a b
forall a b.
(a -> b) -> a -> Forest b -> TreeCursor a b -> TreeCursor a b
treeCursorAddChildNodeAtEndAndSelect a -> b
f a
a []
treeCursorAddChildNodeAtPosAndSelect ::
(a -> b) -> Int -> a -> Forest b -> TreeCursor a b -> TreeCursor a b
treeCursorAddChildNodeAtPosAndSelect :: (a -> b)
-> Int -> a -> Forest b -> TreeCursor a b -> TreeCursor a b
treeCursorAddChildNodeAtPosAndSelect a -> b
f Int
i a
t Forest b
ts TreeCursor a b
tc =
let ([CTree b]
before, [CTree b]
after) = Int -> [CTree b] -> ([CTree b], [CTree b])
forall a. Int -> [a] -> ([a], [a])
splitAt Int
i ([CTree b] -> ([CTree b], [CTree b]))
-> [CTree b] -> ([CTree b], [CTree b])
forall a b. (a -> b) -> a -> b
$ CForest b -> [CTree b]
forall a. CForest a -> [CTree a]
unpackCForest (CForest b -> [CTree b]) -> CForest b -> [CTree b]
forall a b. (a -> b) -> a -> b
$ TreeCursor a b -> CForest b
forall a b. TreeCursor a b -> CForest b
treeBelow TreeCursor a b
tc
in TreeCursor :: forall a b. Maybe (TreeAbove b) -> a -> CForest b -> TreeCursor a b
TreeCursor
{ treeAbove :: Maybe (TreeAbove b)
treeAbove =
TreeAbove b -> Maybe (TreeAbove b)
forall a. a -> Maybe a
Just
TreeAbove :: forall b.
[CTree b] -> Maybe (TreeAbove b) -> b -> [CTree b] -> TreeAbove b
TreeAbove
{ treeAboveLefts :: [CTree b]
treeAboveLefts = [CTree b] -> [CTree b]
forall a. [a] -> [a]
reverse [CTree b]
before,
treeAboveAbove :: Maybe (TreeAbove b)
treeAboveAbove = TreeCursor a b -> Maybe (TreeAbove b)
forall a b. TreeCursor a b -> Maybe (TreeAbove b)
treeAbove TreeCursor a b
tc,
treeAboveNode :: b
treeAboveNode = a -> b
f (TreeCursor a b -> a
forall a b. TreeCursor a b -> a
treeCurrent TreeCursor a b
tc),
treeAboveRights :: [CTree b]
treeAboveRights = [CTree b]
after
},
treeCurrent :: a
treeCurrent = a
t,
treeBelow :: CForest b
treeBelow = Forest b -> CForest b
forall a. Forest a -> CForest a
makeCForest Forest b
ts
}
treeCursorAddChildNodeAtStartAndSelect ::
(a -> b) -> a -> Forest b -> TreeCursor a b -> TreeCursor a b
treeCursorAddChildNodeAtStartAndSelect :: (a -> b) -> a -> Forest b -> TreeCursor a b -> TreeCursor a b
treeCursorAddChildNodeAtStartAndSelect a -> b
f a
t Forest b
ts TreeCursor a b
tc =
TreeCursor :: forall a b. Maybe (TreeAbove b) -> a -> CForest b -> TreeCursor a b
TreeCursor
{ treeAbove :: Maybe (TreeAbove b)
treeAbove =
TreeAbove b -> Maybe (TreeAbove b)
forall a. a -> Maybe a
Just
TreeAbove :: forall b.
[CTree b] -> Maybe (TreeAbove b) -> b -> [CTree b] -> TreeAbove b
TreeAbove
{ treeAboveLefts :: [CTree b]
treeAboveLefts = [],
treeAboveAbove :: Maybe (TreeAbove b)
treeAboveAbove = TreeCursor a b -> Maybe (TreeAbove b)
forall a b. TreeCursor a b -> Maybe (TreeAbove b)
treeAbove TreeCursor a b
tc,
treeAboveNode :: b
treeAboveNode = a -> b
f (TreeCursor a b -> a
forall a b. TreeCursor a b -> a
treeCurrent TreeCursor a b
tc),
treeAboveRights :: [CTree b]
treeAboveRights = CForest b -> [CTree b]
forall a. CForest a -> [CTree a]
unpackCForest (CForest b -> [CTree b]) -> CForest b -> [CTree b]
forall a b. (a -> b) -> a -> b
$ TreeCursor a b -> CForest b
forall a b. TreeCursor a b -> CForest b
treeBelow TreeCursor a b
tc
},
treeCurrent :: a
treeCurrent = a
t,
treeBelow :: CForest b
treeBelow = Forest b -> CForest b
forall a. Forest a -> CForest a
makeCForest Forest b
ts
}
treeCursorAddChildNodeAtEndAndSelect ::
(a -> b) -> a -> Forest b -> TreeCursor a b -> TreeCursor a b
treeCursorAddChildNodeAtEndAndSelect :: (a -> b) -> a -> Forest b -> TreeCursor a b -> TreeCursor a b
treeCursorAddChildNodeAtEndAndSelect a -> b
f a
t Forest b
ts TreeCursor a b
tc =
TreeCursor :: forall a b. Maybe (TreeAbove b) -> a -> CForest b -> TreeCursor a b
TreeCursor
{ treeAbove :: Maybe (TreeAbove b)
treeAbove =
TreeAbove b -> Maybe (TreeAbove b)
forall a. a -> Maybe a
Just
TreeAbove :: forall b.
[CTree b] -> Maybe (TreeAbove b) -> b -> [CTree b] -> TreeAbove b
TreeAbove
{ treeAboveLefts :: [CTree b]
treeAboveLefts = [CTree b] -> [CTree b]
forall a. [a] -> [a]
reverse ([CTree b] -> [CTree b]) -> [CTree b] -> [CTree b]
forall a b. (a -> b) -> a -> b
$ CForest b -> [CTree b]
forall a. CForest a -> [CTree a]
unpackCForest (CForest b -> [CTree b]) -> CForest b -> [CTree b]
forall a b. (a -> b) -> a -> b
$ TreeCursor a b -> CForest b
forall a b. TreeCursor a b -> CForest b
treeBelow TreeCursor a b
tc,
treeAboveAbove :: Maybe (TreeAbove b)
treeAboveAbove = TreeCursor a b -> Maybe (TreeAbove b)
forall a b. TreeCursor a b -> Maybe (TreeAbove b)
treeAbove TreeCursor a b
tc,
treeAboveNode :: b
treeAboveNode = a -> b
f (TreeCursor a b -> a
forall a b. TreeCursor a b -> a
treeCurrent TreeCursor a b
tc),
treeAboveRights :: [CTree b]
treeAboveRights = []
},
treeCurrent :: a
treeCurrent = a
t,
treeBelow :: CForest b
treeBelow = Forest b -> CForest b
forall a. Forest a -> CForest a
makeCForest Forest b
ts
}