Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- type ForestCursor a = ForestCursor a a
- singletonForestCursor :: a -> ForestCursor a b
- makeForestCursor :: NonEmpty (CTree a) -> ForestCursor a
- rebuildForestCursor :: ForestCursor a -> NonEmpty (CTree a)
- drawForestCursor :: (Show a, Show b) => ForestCursor a b -> String
- mapForestCursor :: (a -> b) -> ForestCursor a -> ForestCursor b
- forestCursorListCursorL :: Lens (ForestCursor a b) (ForestCursor c d) (NonEmptyCursor (TreeCursor a b) (CTree b)) (NonEmptyCursor (TreeCursor c d) (CTree d))
- forestCursorSelectedTreeL :: Lens' (ForestCursor a b) (TreeCursor a b)
- forestCursorSelectPrevTreeCursor :: ForestCursor a -> Maybe (ForestCursor a)
- forestCursorSelectNextTreeCursor :: ForestCursor a -> Maybe (ForestCursor a)
- forestCursorSelectFirstTreeCursor :: ForestCursor a -> ForestCursor a
- forestCursorSelectLastTreeCursor :: ForestCursor a -> ForestCursor a
- forestCursorSelectPrev :: ForestCursor a -> Maybe (ForestCursor a)
- forestCursorSelectNext :: ForestCursor a -> Maybe (ForestCursor a)
- forestCursorSelectPrevOnSameLevel :: ForestCursor a -> Maybe (ForestCursor a)
- forestCursorSelectNextOnSameLevel :: ForestCursor a -> Maybe (ForestCursor a)
- forestCursorSelectFirst :: ForestCursor a -> ForestCursor a
- forestCursorSelectLast :: ForestCursor a -> ForestCursor a
- forestCursorSelectFirstOnSameLevel :: ForestCursor a -> ForestCursor a
- forestCursorSelectLastOnSameLevel :: ForestCursor a -> ForestCursor a
- forestCursorSelectAbove :: ForestCursor a -> Maybe (ForestCursor a)
- forestCursorSelectBelowAtPos :: Int -> ForestCursor a -> Maybe (ForestCursor a)
- forestCursorSelectBelowAtStart :: ForestCursor a -> Maybe (ForestCursor a)
- forestCursorSelectBelowAtEnd :: ForestCursor a -> Maybe (ForestCursor a)
- forestCursorOpenCurrentForest :: ForestCursor a b -> Maybe (ForestCursor a b)
- forestCursorCloseCurrentForest :: ForestCursor a b -> Maybe (ForestCursor a b)
- forestCursorToggleCurrentForest :: ForestCursor a b -> Maybe (ForestCursor a b)
- forestCursorOpenCurrentForestRecursively :: ForestCursor a b -> Maybe (ForestCursor a b)
- forestCursorToggleCurrentForestRecursively :: ForestCursor a b -> Maybe (ForestCursor a b)
- forestCursorSelection :: ForestCursor a b -> Int
- forestCursorSelectIndex :: Int -> ForestCursor a -> Maybe (ForestCursor a)
- forestCursorInsertEntireTree :: Tree b -> ForestCursor a b -> ForestCursor a b
- forestCursorInsertAndSelectTreeCursor :: TreeCursor a -> ForestCursor a -> ForestCursor a
- forestCursorAppendEntireTree :: Tree b -> ForestCursor a b -> ForestCursor a b
- forestCursorAppendAndSelectTreeCursor :: TreeCursor a -> ForestCursor a -> ForestCursor a
- forestCursorInsertTree :: Tree b -> ForestCursor a b -> ForestCursor a b
- forestCursorAppendTree :: Tree b -> ForestCursor a b -> ForestCursor a b
- forestCursorInsertAndSelectTree :: Tree a -> ForestCursor a -> ForestCursor a
- forestCursorAppendAndSelectTree :: Tree a -> ForestCursor a -> ForestCursor a
- forestCursorInsert :: b -> ForestCursor a b -> ForestCursor a b
- forestCursorAppend :: b -> ForestCursor a b -> ForestCursor a b
- forestCursorInsertAndSelect :: a -> ForestCursor a -> ForestCursor a
- forestCursorAppendAndSelect :: a -> ForestCursor a -> ForestCursor a
- forestCursorInsertNodeSingleAndSelect :: a -> ForestCursor a -> ForestCursor a
- forestCursorAppendNodeSingleAndSelect :: a -> ForestCursor a -> ForestCursor a
- forestCursorInsertNodeAndSelect :: a -> CForest a -> ForestCursor a -> ForestCursor a
- forestCursorAppendNodeAndSelect :: a -> CForest a -> ForestCursor a -> ForestCursor a
- forestCursorAddChildTreeToNodeAtPos :: Int -> Tree b -> ForestCursor a b -> ForestCursor a b
- forestCursorAddChildTreeToNodeAtStart :: Tree b -> ForestCursor a b -> ForestCursor a b
- forestCursorAddChildTreeToNodeAtEnd :: Tree b -> ForestCursor a b -> ForestCursor a b
- forestCursorAddChildToNodeAtPos :: Int -> b -> ForestCursor a b -> ForestCursor a b
- forestCursorAddChildToNodeAtStart :: b -> ForestCursor a b -> ForestCursor a b
- forestCursorAddChildToNodeAtEnd :: b -> ForestCursor a b -> ForestCursor a b
- forestCursorAddChildTreeToNodeAtPosAndSelect :: Int -> Tree a -> ForestCursor a -> ForestCursor a
- forestCursorAddChildTreeToNodeAtStartAndSelect :: Tree a -> ForestCursor a -> ForestCursor a
- forestCursorAddChildTreeToNodeAtEndAndSelect :: Tree a -> ForestCursor a -> ForestCursor a
- forestCursorAddChildToNodeAtPosAndSelect :: Int -> a -> ForestCursor a -> ForestCursor a
- forestCursorAddChildToNodeAtStartAndSelect :: a -> ForestCursor a -> ForestCursor a
- forestCursorAddChildToNodeAtEndAndSelect :: a -> ForestCursor a -> ForestCursor a
- forestCursorAddChildNodeSingleToNodeAtPosAndSelect :: Int -> a -> ForestCursor a -> ForestCursor a
- forestCursorAddChildNodeSingleToNodeAtStartAndSelect :: a -> ForestCursor a -> ForestCursor a
- forestCursorAddChildNodeSingleToNodeAtEndAndSelect :: a -> ForestCursor a -> ForestCursor a
- forestCursorAddChildNodeToNodeAtPosAndSelect :: Int -> a -> Forest a -> ForestCursor a -> ForestCursor a
- forestCursorAddChildNodeToNodeAtStartAndSelect :: a -> Forest a -> ForestCursor a -> ForestCursor a
- forestCursorAddChildNodeToNodeAtEndAndSelect :: a -> Forest a -> ForestCursor a -> ForestCursor a
- forestCursorRemoveElemAndSelectPrev :: ForestCursor a -> Maybe (DeleteOrUpdate (ForestCursor a))
- forestCursorDeleteElemAndSelectNext :: ForestCursor a -> Maybe (DeleteOrUpdate (ForestCursor a))
- forestCursorRemoveElem :: ForestCursor a -> DeleteOrUpdate (ForestCursor a)
- forestCursorDeleteElem :: ForestCursor a -> DeleteOrUpdate (ForestCursor a)
- forestCursorRemoveSubTreeAndSelectPrev :: ForestCursor a -> Maybe (DeleteOrUpdate (ForestCursor a))
- forestCursorDeleteSubTreeAndSelectNext :: ForestCursor a -> Maybe (DeleteOrUpdate (ForestCursor a))
- forestCursorRemoveSubTree :: ForestCursor a -> DeleteOrUpdate (ForestCursor a)
- forestCursorDeleteSubTree :: ForestCursor a -> DeleteOrUpdate (ForestCursor a)
- forestCursorAddRoot :: ForestCursor a -> a -> TreeCursor a
- forestCursorSwapPrev :: ForestCursor a b -> Maybe (ForestCursor a b)
- forestCursorSwapNext :: ForestCursor a b -> Maybe (ForestCursor a b)
- forestCursorPromoteElem :: ForestCursor a -> Maybe (ForestCursor a)
- forestCursorPromoteSubTree :: ForestCursor a -> Maybe (ForestCursor a)
- forestCursorDemoteElem :: ForestCursor a -> Maybe (ForestCursor a)
- forestCursorDemoteSubTree :: ForestCursor a -> Maybe (ForestCursor a)
- forestCursorDemoteElemUnder :: b -> b -> ForestCursor a b -> ForestCursor a b
- forestCursorDemoteSubTreeUnder :: b -> ForestCursor a b -> ForestCursor a b
- data CTree a = CNode !a (CForest a)
- makeCTree :: Tree a -> CTree a
- cTree :: Bool -> Tree a -> CTree a
- rebuildCTree :: CTree a -> Tree a
- data CForest a
- = EmptyCForest
- | ClosedForest !(NonEmpty (Tree a))
- | OpenForest !(NonEmpty (CTree a))
- makeCForest :: Forest a -> CForest a
- cForest :: Bool -> Forest a -> CForest a
- rebuildCForest :: CForest a -> Forest a
Documentation
type ForestCursor a = ForestCursor a a Source #
singletonForestCursor :: a -> ForestCursor a b Source #
makeForestCursor :: NonEmpty (CTree a) -> ForestCursor a Source #
rebuildForestCursor :: ForestCursor a -> NonEmpty (CTree a) Source #
drawForestCursor :: (Show a, Show b) => ForestCursor a b -> String Source #
mapForestCursor :: (a -> b) -> ForestCursor a -> ForestCursor b Source #
forestCursorListCursorL :: Lens (ForestCursor a b) (ForestCursor c d) (NonEmptyCursor (TreeCursor a b) (CTree b)) (NonEmptyCursor (TreeCursor c d) (CTree d)) Source #
forestCursorSelectedTreeL :: Lens' (ForestCursor a b) (TreeCursor a b) Source #
forestCursorSelectPrevTreeCursor :: ForestCursor a -> Maybe (ForestCursor a) Source #
forestCursorSelectNextTreeCursor :: ForestCursor a -> Maybe (ForestCursor a) Source #
forestCursorSelectPrev :: ForestCursor a -> Maybe (ForestCursor a) Source #
forestCursorSelectNext :: ForestCursor a -> Maybe (ForestCursor a) Source #
forestCursorSelectFirst :: ForestCursor a -> ForestCursor a Source #
forestCursorSelectLast :: ForestCursor a -> ForestCursor a Source #
forestCursorSelectAbove :: ForestCursor a -> Maybe (ForestCursor a) Source #
forestCursorSelectBelowAtPos :: Int -> ForestCursor a -> Maybe (ForestCursor a) Source #
forestCursorSelectBelowAtStart :: ForestCursor a -> Maybe (ForestCursor a) Source #
forestCursorSelectBelowAtEnd :: ForestCursor a -> Maybe (ForestCursor a) Source #
forestCursorOpenCurrentForest :: ForestCursor a b -> Maybe (ForestCursor a b) Source #
forestCursorCloseCurrentForest :: ForestCursor a b -> Maybe (ForestCursor a b) Source #
forestCursorToggleCurrentForest :: ForestCursor a b -> Maybe (ForestCursor a b) Source #
forestCursorOpenCurrentForestRecursively :: ForestCursor a b -> Maybe (ForestCursor a b) Source #
forestCursorToggleCurrentForestRecursively :: ForestCursor a b -> Maybe (ForestCursor a b) Source #
forestCursorSelection :: ForestCursor a b -> Int Source #
forestCursorSelectIndex :: Int -> ForestCursor a -> Maybe (ForestCursor a) Source #
forestCursorInsertEntireTree :: Tree b -> ForestCursor a b -> ForestCursor a b Source #
forestCursorInsertAndSelectTreeCursor :: TreeCursor a -> ForestCursor a -> ForestCursor a Source #
forestCursorAppendEntireTree :: Tree b -> ForestCursor a b -> ForestCursor a b Source #
forestCursorAppendAndSelectTreeCursor :: TreeCursor a -> ForestCursor a -> ForestCursor a Source #
forestCursorInsertTree :: Tree b -> ForestCursor a b -> ForestCursor a b Source #
forestCursorAppendTree :: Tree b -> ForestCursor a b -> ForestCursor a b Source #
forestCursorInsertAndSelectTree :: Tree a -> ForestCursor a -> ForestCursor a Source #
forestCursorAppendAndSelectTree :: Tree a -> ForestCursor a -> ForestCursor a Source #
forestCursorInsert :: b -> ForestCursor a b -> ForestCursor a b Source #
forestCursorAppend :: b -> ForestCursor a b -> ForestCursor a b Source #
forestCursorInsertAndSelect :: a -> ForestCursor a -> ForestCursor a Source #
forestCursorAppendAndSelect :: a -> ForestCursor a -> ForestCursor a Source #
forestCursorInsertNodeSingleAndSelect :: a -> ForestCursor a -> ForestCursor a Source #
forestCursorAppendNodeSingleAndSelect :: a -> ForestCursor a -> ForestCursor a Source #
forestCursorInsertNodeAndSelect :: a -> CForest a -> ForestCursor a -> ForestCursor a Source #
forestCursorAppendNodeAndSelect :: a -> CForest a -> ForestCursor a -> ForestCursor a Source #
forestCursorAddChildTreeToNodeAtPos :: Int -> Tree b -> ForestCursor a b -> ForestCursor a b Source #
forestCursorAddChildTreeToNodeAtStart :: Tree b -> ForestCursor a b -> ForestCursor a b Source #
forestCursorAddChildTreeToNodeAtEnd :: Tree b -> ForestCursor a b -> ForestCursor a b Source #
forestCursorAddChildToNodeAtPos :: Int -> b -> ForestCursor a b -> ForestCursor a b Source #
forestCursorAddChildToNodeAtStart :: b -> ForestCursor a b -> ForestCursor a b Source #
forestCursorAddChildToNodeAtEnd :: b -> ForestCursor a b -> ForestCursor a b Source #
forestCursorAddChildTreeToNodeAtPosAndSelect :: Int -> Tree a -> ForestCursor a -> ForestCursor a Source #
forestCursorAddChildTreeToNodeAtStartAndSelect :: Tree a -> ForestCursor a -> ForestCursor a Source #
forestCursorAddChildTreeToNodeAtEndAndSelect :: Tree a -> ForestCursor a -> ForestCursor a Source #
forestCursorAddChildToNodeAtPosAndSelect :: Int -> a -> ForestCursor a -> ForestCursor a Source #
forestCursorAddChildToNodeAtStartAndSelect :: a -> ForestCursor a -> ForestCursor a Source #
forestCursorAddChildToNodeAtEndAndSelect :: a -> ForestCursor a -> ForestCursor a Source #
forestCursorAddChildNodeSingleToNodeAtPosAndSelect :: Int -> a -> ForestCursor a -> ForestCursor a Source #
forestCursorAddChildNodeSingleToNodeAtStartAndSelect :: a -> ForestCursor a -> ForestCursor a Source #
forestCursorAddChildNodeSingleToNodeAtEndAndSelect :: a -> ForestCursor a -> ForestCursor a Source #
forestCursorAddChildNodeToNodeAtPosAndSelect :: Int -> a -> Forest a -> ForestCursor a -> ForestCursor a Source #
forestCursorAddChildNodeToNodeAtStartAndSelect :: a -> Forest a -> ForestCursor a -> ForestCursor a Source #
forestCursorAddChildNodeToNodeAtEndAndSelect :: a -> Forest a -> ForestCursor a -> ForestCursor a Source #
forestCursorRemoveElemAndSelectPrev :: ForestCursor a -> Maybe (DeleteOrUpdate (ForestCursor a)) Source #
forestCursorDeleteElemAndSelectNext :: ForestCursor a -> Maybe (DeleteOrUpdate (ForestCursor a)) Source #
forestCursorRemoveElem :: ForestCursor a -> DeleteOrUpdate (ForestCursor a) Source #
forestCursorDeleteElem :: ForestCursor a -> DeleteOrUpdate (ForestCursor a) Source #
forestCursorRemoveSubTreeAndSelectPrev :: ForestCursor a -> Maybe (DeleteOrUpdate (ForestCursor a)) Source #
forestCursorDeleteSubTreeAndSelectNext :: ForestCursor a -> Maybe (DeleteOrUpdate (ForestCursor a)) Source #
forestCursorAddRoot :: ForestCursor a -> a -> TreeCursor a Source #
forestCursorSwapPrev :: ForestCursor a b -> Maybe (ForestCursor a b) Source #
Swaps the current node with the previous node on the same level
Example:
Before:
- a - b <--
After:
- b <-- - a
forestCursorSwapNext :: ForestCursor a b -> Maybe (ForestCursor a b) Source #
Swaps the current node with the next node on the same level
Example:
Before:
- a <-- - b
After:
- b - a <--
forestCursorPromoteElem :: ForestCursor a -> Maybe (ForestCursor a) Source #
forestCursorPromoteSubTree :: ForestCursor a -> Maybe (ForestCursor a) Source #
forestCursorDemoteElem :: ForestCursor a -> Maybe (ForestCursor a) Source #
forestCursorDemoteSubTree :: ForestCursor a -> Maybe (ForestCursor a) Source #
forestCursorDemoteElemUnder :: b -> b -> ForestCursor a b -> ForestCursor a b Source #
Demotes the current node to the level of its children, by adding two roots. One for the current node and one for its children that are left behind.
Example:
Before:
- a <-- |- b
After:
- <given element 1> |- a <-- - <given element 2> |- b
forestCursorDemoteSubTreeUnder :: b -> ForestCursor a b -> ForestCursor a b Source #
Demotes the current subtree to the level of its children, by adding a root.
Example:
Before:
a <-- |- b
After:
<given element> |- a <-- |- b
Instances
rebuildCTree :: CTree a -> Tree a Source #
EmptyCForest | |
ClosedForest !(NonEmpty (Tree a)) | |
OpenForest !(NonEmpty (CTree a)) |
Instances
makeCForest :: Forest a -> CForest a Source #
rebuildCForest :: CForest a -> Forest a Source #