Safe Haskell | None |
---|---|
Language | Haskell2010 |
Cursor.Simple.Tree
Synopsis
- type TreeCursor a = TreeCursor a a
- data TreeAbove b = TreeAbove {
- treeAboveLefts :: ![CTree b]
- treeAboveAbove :: !(Maybe (TreeAbove b))
- treeAboveNode :: !b
- treeAboveRights :: ![CTree b]
- singletonTreeCursor :: a -> TreeCursor a
- makeTreeCursor :: CTree a -> TreeCursor a
- makeNodeTreeCursor :: a -> CForest b -> TreeCursor a b
- makeTreeCursorWithSelection :: TreeCursorSelection -> CTree a -> Maybe (TreeCursor a)
- rebuildTreeCursor :: TreeCursor a -> CTree a
- drawTreeCursor :: (Show a, Show b) => TreeCursor a b -> String
- mapTreeCursor :: (a -> b) -> TreeCursor a -> TreeCursor b
- treeCursorAboveL :: forall a b f. Functor f => (Maybe (TreeAbove b) -> f (Maybe (TreeAbove b))) -> TreeCursor a b -> f (TreeCursor a b)
- treeCursorCurrentL :: forall a b a' f. Functor f => (a -> f a') -> TreeCursor a b -> f (TreeCursor a' b)
- treeCursorBelowL :: forall a b f. Functor f => (CForest b -> f (CForest b)) -> TreeCursor a b -> f (TreeCursor a b)
- treeAboveLeftsL :: forall b f. Functor f => ([CTree b] -> f [CTree b]) -> TreeAbove b -> f (TreeAbove b)
- treeAboveAboveL :: forall b f. Functor f => (Maybe (TreeAbove b) -> f (Maybe (TreeAbove b))) -> TreeAbove b -> f (TreeAbove b)
- treeAboveNodeL :: forall b f. Functor f => (b -> f b) -> TreeAbove b -> f (TreeAbove b)
- treeAboveRightsL :: forall b f. Functor f => ([CTree b] -> f [CTree b]) -> TreeAbove b -> f (TreeAbove b)
- treeCursorWithPointer :: (Show a, Show b) => TreeCursor a b -> Tree String
- treeCursorSelection :: TreeCursor a b -> TreeCursorSelection
- data TreeCursorSelection
- treeCursorSelect :: TreeCursorSelection -> TreeCursor a -> Maybe (TreeCursor a)
- treeCursorSelectPrev :: TreeCursor a -> Maybe (TreeCursor a)
- treeCursorSelectNext :: TreeCursor a -> Maybe (TreeCursor a)
- treeCursorSelectFirst :: TreeCursor a -> TreeCursor a
- treeCursorSelectLast :: TreeCursor a -> TreeCursor a
- treeCursorSelectAbove :: TreeCursor a -> Maybe (TreeCursor a)
- treeCursorSelectBelowAtPos :: Int -> TreeCursor a -> Maybe (TreeCursor a)
- treeCursorSelectBelowAtStart :: TreeCursor a -> Maybe (TreeCursor a)
- treeCursorSelectBelowAtEnd :: TreeCursor a -> Maybe (TreeCursor a)
- treeCursorSelectBelowAtStartRecursively :: TreeCursor a -> Maybe (TreeCursor a)
- treeCursorSelectBelowAtEndRecursively :: TreeCursor a -> Maybe (TreeCursor a)
- treeCursorSelectPrevOnSameLevel :: TreeCursor a -> Maybe (TreeCursor a)
- treeCursorSelectNextOnSameLevel :: TreeCursor a -> Maybe (TreeCursor a)
- treeCursorSelectFirstOnSameLevel :: TreeCursor a -> TreeCursor a
- treeCursorSelectLastOnSameLevel :: TreeCursor a -> TreeCursor a
- treeCursorSelectAbovePrev :: TreeCursor a -> Maybe (TreeCursor a)
- treeCursorSelectAboveNext :: TreeCursor a -> Maybe (TreeCursor a)
- treeCursorOpenCurrentForest :: TreeCursor a b -> Maybe (TreeCursor a b)
- treeCursorCloseCurrentForest :: TreeCursor a b -> Maybe (TreeCursor a b)
- treeCursorToggleCurrentForest :: TreeCursor a b -> Maybe (TreeCursor a b)
- treeCursorOpenCurrentForestRecursively :: TreeCursor a b -> Maybe (TreeCursor a b)
- treeCursorToggleCurrentForestRecursively :: TreeCursor a b -> Maybe (TreeCursor a b)
- treeCursorInsert :: Tree b -> TreeCursor a b -> Maybe (TreeCursor a b)
- treeCursorInsertAndSelect :: Tree a -> TreeCursor a -> Maybe (TreeCursor a)
- treeCursorInsertNodeSingleAndSelect :: a -> TreeCursor a -> Maybe (TreeCursor a)
- treeCursorInsertNodeAndSelect :: a -> CForest a -> TreeCursor a -> Maybe (TreeCursor a)
- treeCursorAppend :: Tree b -> TreeCursor a b -> Maybe (TreeCursor a b)
- treeCursorAppendAndSelect :: Tree a -> TreeCursor a -> Maybe (TreeCursor a)
- treeCursorAppendNodeSingleAndSelect :: a -> TreeCursor a -> Maybe (TreeCursor a)
- treeCursorAppendNodeAndSelect :: a -> CForest a -> TreeCursor a -> Maybe (TreeCursor a)
- treeCursorAddChildAtPos :: Int -> Tree b -> TreeCursor a b -> TreeCursor a b
- treeCursorAddChildAtStart :: Tree b -> TreeCursor a b -> TreeCursor a b
- treeCursorAddChildAtEnd :: Tree b -> TreeCursor a b -> TreeCursor a b
- treeCursorAddChildAtPosAndSelect :: Int -> Tree a -> TreeCursor a -> TreeCursor a
- treeCursorAddChildAtStartAndSelect :: Tree a -> TreeCursor a -> TreeCursor a
- treeCursorAddChildAtEndAndSelect :: Tree a -> TreeCursor a -> TreeCursor a
- treeCursorAddChildNodeSingleAtPosAndSelect :: Int -> a -> TreeCursor a -> TreeCursor a
- treeCursorAddChildNodeSingleAtStartAndSelect :: a -> TreeCursor a -> TreeCursor a
- treeCursorAddChildNodeSingleAtEndAndSelect :: a -> TreeCursor a -> TreeCursor a
- treeCursorAddChildNodeAtPosAndSelect :: Int -> a -> Forest a -> TreeCursor a -> TreeCursor a
- treeCursorAddChildNodeAtStartAndSelect :: a -> Forest a -> TreeCursor a -> TreeCursor a
- treeCursorAddChildNodeAtEndAndSelect :: a -> Forest a -> TreeCursor a -> TreeCursor a
- treeCursorDeleteSubTreeAndSelectPrevious :: TreeCursor a -> Maybe (DeleteOrUpdate (TreeCursor a))
- treeCursorDeleteSubTreeAndSelectNext :: TreeCursor a -> Maybe (DeleteOrUpdate (TreeCursor a))
- treeCursorDeleteSubTreeAndSelectAbove :: TreeCursor a -> DeleteOrUpdate (TreeCursor a)
- treeCursorRemoveSubTree :: TreeCursor a -> DeleteOrUpdate (TreeCursor a)
- treeCursorDeleteSubTree :: TreeCursor a -> DeleteOrUpdate (TreeCursor a)
- treeCursorDeleteElemAndSelectPrevious :: TreeCursor a -> Maybe (DeleteOrUpdate (TreeCursor a))
- treeCursorDeleteElemAndSelectNext :: TreeCursor a -> Maybe (DeleteOrUpdate (TreeCursor a))
- treeCursorDeleteElemAndSelectAbove :: TreeCursor a -> Maybe (DeleteOrUpdate (TreeCursor a))
- treeCursorRemoveElem :: TreeCursor a -> DeleteOrUpdate (TreeCursor a)
- treeCursorDeleteElem :: TreeCursor a -> DeleteOrUpdate (TreeCursor a)
- treeCursorSwapPrev :: TreeCursor a b -> SwapResult (TreeCursor a b)
- treeCursorSwapNext :: TreeCursor a b -> SwapResult (TreeCursor a b)
- data SwapResult a
- treeCursorPromoteElem :: TreeCursor a -> PromoteElemResult (TreeCursor a)
- data PromoteElemResult a
- treeCursorPromoteSubTree :: TreeCursor a -> PromoteResult (TreeCursor a)
- data PromoteResult a
- treeCursorDemoteElem :: TreeCursor a -> DemoteResult (TreeCursor a)
- treeCursorDemoteSubTree :: TreeCursor a -> DemoteResult (TreeCursor a)
- data DemoteResult a
- treeCursorDemoteElemUnder :: b -> b -> TreeCursor a b -> Maybe (TreeCursor a b)
- treeCursorDemoteSubTreeUnder :: b -> TreeCursor a b -> TreeCursor a b
- data CTree a = CNode !a (CForest a)
- data CForest a
- makeCTree :: Tree a -> CTree a
- cTree :: Bool -> Tree a -> CTree a
- rebuildCTree :: CTree a -> Tree a
Documentation
type TreeCursor a = TreeCursor a a Source #
Constructors
TreeAbove | |
Fields
|
Instances
singletonTreeCursor :: a -> TreeCursor a Source #
makeTreeCursor :: CTree a -> TreeCursor a Source #
makeNodeTreeCursor :: a -> CForest b -> TreeCursor a b Source #
makeTreeCursorWithSelection :: TreeCursorSelection -> CTree a -> Maybe (TreeCursor a) Source #
rebuildTreeCursor :: TreeCursor a -> CTree a Source #
drawTreeCursor :: (Show a, Show b) => TreeCursor a b -> String Source #
mapTreeCursor :: (a -> b) -> TreeCursor a -> TreeCursor b Source #
treeCursorAboveL :: forall a b f. Functor f => (Maybe (TreeAbove b) -> f (Maybe (TreeAbove b))) -> TreeCursor a b -> f (TreeCursor a b) Source #
treeCursorCurrentL :: forall a b a' f. Functor f => (a -> f a') -> TreeCursor a b -> f (TreeCursor a' b) Source #
treeCursorBelowL :: forall a b f. Functor f => (CForest b -> f (CForest b)) -> TreeCursor a b -> f (TreeCursor a b) Source #
treeAboveLeftsL :: forall b f. Functor f => ([CTree b] -> f [CTree b]) -> TreeAbove b -> f (TreeAbove b) Source #
treeAboveAboveL :: forall b f. Functor f => (Maybe (TreeAbove b) -> f (Maybe (TreeAbove b))) -> TreeAbove b -> f (TreeAbove b) Source #
treeAboveRightsL :: forall b f. Functor f => ([CTree b] -> f [CTree b]) -> TreeAbove b -> f (TreeAbove b) Source #
treeCursorWithPointer :: (Show a, Show b) => TreeCursor a b -> Tree String Source #
treeCursorSelection :: TreeCursor a b -> TreeCursorSelection Source #
data TreeCursorSelection Source #
Constructors
SelectNode | |
SelectChild !Int !TreeCursorSelection |
Instances
NFData TreeCursorSelection Source # | |||||
Defined in Cursor.Tree.Types Methods rnf :: TreeCursorSelection -> () # | |||||
Generic TreeCursorSelection Source # | |||||
Defined in Cursor.Tree.Types Associated Types
Methods from :: TreeCursorSelection -> Rep TreeCursorSelection x # to :: Rep TreeCursorSelection x -> TreeCursorSelection # | |||||
Show TreeCursorSelection Source # | |||||
Defined in Cursor.Tree.Types Methods showsPrec :: Int -> TreeCursorSelection -> ShowS # show :: TreeCursorSelection -> String # showList :: [TreeCursorSelection] -> ShowS # | |||||
Eq TreeCursorSelection Source # | |||||
Defined in Cursor.Tree.Types Methods (==) :: TreeCursorSelection -> TreeCursorSelection -> Bool # (/=) :: TreeCursorSelection -> TreeCursorSelection -> Bool # | |||||
Validity TreeCursorSelection Source # | |||||
Defined in Cursor.Tree.Types Methods | |||||
type Rep TreeCursorSelection Source # | |||||
Defined in Cursor.Tree.Types type Rep TreeCursorSelection = D1 ('MetaData "TreeCursorSelection" "Cursor.Tree.Types" "cursor-0.3.2.0-DsqeuvBEfePHA4N8n3HFEH" 'False) (C1 ('MetaCons "SelectNode" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SelectChild" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TreeCursorSelection))) |
treeCursorSelect :: TreeCursorSelection -> TreeCursor a -> Maybe (TreeCursor a) Source #
treeCursorSelectPrev :: TreeCursor a -> Maybe (TreeCursor a) Source #
treeCursorSelectNext :: TreeCursor a -> Maybe (TreeCursor a) Source #
treeCursorSelectFirst :: TreeCursor a -> TreeCursor a Source #
treeCursorSelectLast :: TreeCursor a -> TreeCursor a Source #
treeCursorSelectAbove :: TreeCursor a -> Maybe (TreeCursor a) Source #
treeCursorSelectBelowAtPos :: Int -> TreeCursor a -> Maybe (TreeCursor a) Source #
treeCursorSelectBelowAtStart :: TreeCursor a -> Maybe (TreeCursor a) Source #
treeCursorSelectBelowAtEnd :: TreeCursor a -> Maybe (TreeCursor a) Source #
treeCursorSelectPrevOnSameLevel :: TreeCursor a -> Maybe (TreeCursor a) Source #
treeCursorSelectNextOnSameLevel :: TreeCursor a -> Maybe (TreeCursor a) Source #
treeCursorSelectAbovePrev :: TreeCursor a -> Maybe (TreeCursor a) Source #
Go back and down as far as necessary to find a previous element on a level below
treeCursorSelectAboveNext :: TreeCursor a -> Maybe (TreeCursor a) Source #
Go up as far as necessary to find a next element on a level above and forward
Note: This will fail if there is a next node on the same level or any node below the current node
treeCursorOpenCurrentForest :: TreeCursor a b -> Maybe (TreeCursor a b) Source #
treeCursorCloseCurrentForest :: TreeCursor a b -> Maybe (TreeCursor a b) Source #
treeCursorToggleCurrentForest :: TreeCursor a b -> Maybe (TreeCursor a b) Source #
treeCursorOpenCurrentForestRecursively :: TreeCursor a b -> Maybe (TreeCursor a b) Source #
treeCursorToggleCurrentForestRecursively :: TreeCursor a b -> Maybe (TreeCursor a b) Source #
treeCursorInsert :: Tree b -> TreeCursor a b -> Maybe (TreeCursor a b) Source #
treeCursorInsertAndSelect :: Tree a -> TreeCursor a -> Maybe (TreeCursor a) Source #
treeCursorInsertNodeSingleAndSelect :: a -> TreeCursor a -> Maybe (TreeCursor a) Source #
treeCursorInsertNodeAndSelect :: a -> CForest a -> TreeCursor a -> Maybe (TreeCursor a) Source #
treeCursorAppend :: Tree b -> TreeCursor a b -> Maybe (TreeCursor a b) Source #
treeCursorAppendAndSelect :: Tree a -> TreeCursor a -> Maybe (TreeCursor a) Source #
treeCursorAppendNodeSingleAndSelect :: a -> TreeCursor a -> Maybe (TreeCursor a) Source #
treeCursorAppendNodeAndSelect :: a -> CForest a -> TreeCursor a -> Maybe (TreeCursor a) Source #
treeCursorAddChildAtPos :: Int -> Tree b -> TreeCursor a b -> TreeCursor a b Source #
treeCursorAddChildAtStart :: Tree b -> TreeCursor a b -> TreeCursor a b Source #
treeCursorAddChildAtEnd :: Tree b -> TreeCursor a b -> TreeCursor a b Source #
treeCursorAddChildAtPosAndSelect :: Int -> Tree a -> TreeCursor a -> TreeCursor a Source #
treeCursorAddChildAtStartAndSelect :: Tree a -> TreeCursor a -> TreeCursor a Source #
treeCursorAddChildAtEndAndSelect :: Tree a -> TreeCursor a -> TreeCursor a Source #
treeCursorAddChildNodeSingleAtPosAndSelect :: Int -> a -> TreeCursor a -> TreeCursor a Source #
treeCursorAddChildNodeSingleAtStartAndSelect :: a -> TreeCursor a -> TreeCursor a Source #
treeCursorAddChildNodeSingleAtEndAndSelect :: a -> TreeCursor a -> TreeCursor a Source #
treeCursorAddChildNodeAtPosAndSelect :: Int -> a -> Forest a -> TreeCursor a -> TreeCursor a Source #
treeCursorAddChildNodeAtStartAndSelect :: a -> Forest a -> TreeCursor a -> TreeCursor a Source #
treeCursorAddChildNodeAtEndAndSelect :: a -> Forest a -> TreeCursor a -> TreeCursor a Source #
treeCursorDeleteSubTreeAndSelectPrevious :: TreeCursor a -> Maybe (DeleteOrUpdate (TreeCursor a)) Source #
treeCursorDeleteSubTreeAndSelectNext :: TreeCursor a -> Maybe (DeleteOrUpdate (TreeCursor a)) Source #
treeCursorRemoveSubTree :: TreeCursor a -> DeleteOrUpdate (TreeCursor a) Source #
treeCursorDeleteSubTree :: TreeCursor a -> DeleteOrUpdate (TreeCursor a) Source #
treeCursorDeleteElemAndSelectPrevious :: TreeCursor a -> Maybe (DeleteOrUpdate (TreeCursor a)) Source #
treeCursorDeleteElemAndSelectNext :: TreeCursor a -> Maybe (DeleteOrUpdate (TreeCursor a)) Source #
treeCursorDeleteElemAndSelectAbove :: TreeCursor a -> Maybe (DeleteOrUpdate (TreeCursor a)) Source #
treeCursorRemoveElem :: TreeCursor a -> DeleteOrUpdate (TreeCursor a) Source #
treeCursorDeleteElem :: TreeCursor a -> DeleteOrUpdate (TreeCursor a) Source #
treeCursorSwapPrev :: TreeCursor a b -> SwapResult (TreeCursor a b) Source #
Swaps the current node with the previous node on the same level
Example:
Before:
p |- a |- b <--
After:
p |- b <-- |- a
treeCursorSwapNext :: TreeCursor a b -> SwapResult (TreeCursor a b) Source #
Swaps the current node with the next node on the same level
Example:
Before:
p |- a <-- |- b
After:
p |- b |- a <--
data SwapResult a Source #
Constructors
SwapperIsTopNode | |
NoSiblingsToSwapWith | |
Swapped a |
Instances
Functor SwapResult Source # | |||||
Defined in Cursor.Tree.Swap Methods fmap :: (a -> b) -> SwapResult a -> SwapResult b # (<$) :: a -> SwapResult b -> SwapResult a # | |||||
NFData a => NFData (SwapResult a) Source # | |||||
Defined in Cursor.Tree.Swap Methods rnf :: SwapResult a -> () # | |||||
Generic (SwapResult a) Source # | |||||
Defined in Cursor.Tree.Swap Associated Types
| |||||
Show a => Show (SwapResult a) Source # | |||||
Defined in Cursor.Tree.Swap Methods showsPrec :: Int -> SwapResult a -> ShowS # show :: SwapResult a -> String # showList :: [SwapResult a] -> ShowS # | |||||
Eq a => Eq (SwapResult a) Source # | |||||
Defined in Cursor.Tree.Swap | |||||
Validity a => Validity (SwapResult a) Source # | |||||
Defined in Cursor.Tree.Swap Methods validate :: SwapResult a -> Validation # | |||||
type Rep (SwapResult a) Source # | |||||
Defined in Cursor.Tree.Swap type Rep (SwapResult a) = D1 ('MetaData "SwapResult" "Cursor.Tree.Swap" "cursor-0.3.2.0-DsqeuvBEfePHA4N8n3HFEH" 'False) (C1 ('MetaCons "SwapperIsTopNode" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "NoSiblingsToSwapWith" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Swapped" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))) |
treeCursorPromoteElem :: TreeCursor a -> PromoteElemResult (TreeCursor a) Source #
data PromoteElemResult a Source #
Constructors
CannotPromoteTopElem | |
NoGrandparentToPromoteElemUnder | |
NoSiblingsToAdoptChildren | |
PromotedElem a |
Instances
Applicative PromoteElemResult Source # | |||||
Defined in Cursor.Tree.Promote Methods pure :: a -> PromoteElemResult a # (<*>) :: PromoteElemResult (a -> b) -> PromoteElemResult a -> PromoteElemResult b # liftA2 :: (a -> b -> c) -> PromoteElemResult a -> PromoteElemResult b -> PromoteElemResult c # (*>) :: PromoteElemResult a -> PromoteElemResult b -> PromoteElemResult b # (<*) :: PromoteElemResult a -> PromoteElemResult b -> PromoteElemResult a # | |||||
Functor PromoteElemResult Source # | |||||
Defined in Cursor.Tree.Promote Methods fmap :: (a -> b) -> PromoteElemResult a -> PromoteElemResult b # (<$) :: a -> PromoteElemResult b -> PromoteElemResult a # | |||||
Monad PromoteElemResult Source # | |||||
Defined in Cursor.Tree.Promote Methods (>>=) :: PromoteElemResult a -> (a -> PromoteElemResult b) -> PromoteElemResult b # (>>) :: PromoteElemResult a -> PromoteElemResult b -> PromoteElemResult b # return :: a -> PromoteElemResult a # | |||||
NFData a => NFData (PromoteElemResult a) Source # | |||||
Defined in Cursor.Tree.Promote Methods rnf :: PromoteElemResult a -> () # | |||||
Generic (PromoteElemResult a) Source # | |||||
Defined in Cursor.Tree.Promote Associated Types
Methods from :: PromoteElemResult a -> Rep (PromoteElemResult a) x # to :: Rep (PromoteElemResult a) x -> PromoteElemResult a # | |||||
Show a => Show (PromoteElemResult a) Source # | |||||
Defined in Cursor.Tree.Promote Methods showsPrec :: Int -> PromoteElemResult a -> ShowS # show :: PromoteElemResult a -> String # showList :: [PromoteElemResult a] -> ShowS # | |||||
Eq a => Eq (PromoteElemResult a) Source # | |||||
Defined in Cursor.Tree.Promote Methods (==) :: PromoteElemResult a -> PromoteElemResult a -> Bool # (/=) :: PromoteElemResult a -> PromoteElemResult a -> Bool # | |||||
Validity a => Validity (PromoteElemResult a) Source # | |||||
Defined in Cursor.Tree.Promote Methods validate :: PromoteElemResult a -> Validation # | |||||
type Rep (PromoteElemResult a) Source # | |||||
Defined in Cursor.Tree.Promote type Rep (PromoteElemResult a) = D1 ('MetaData "PromoteElemResult" "Cursor.Tree.Promote" "cursor-0.3.2.0-DsqeuvBEfePHA4N8n3HFEH" 'False) ((C1 ('MetaCons "CannotPromoteTopElem" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NoGrandparentToPromoteElemUnder" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "NoSiblingsToAdoptChildren" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PromotedElem" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))) |
treeCursorPromoteSubTree :: TreeCursor a -> PromoteResult (TreeCursor a) Source #
data PromoteResult a Source #
Constructors
CannotPromoteTopNode | |
NoGrandparentToPromoteUnder | |
Promoted a |
Instances
Applicative PromoteResult Source # | |||||
Defined in Cursor.Tree.Promote Methods pure :: a -> PromoteResult a # (<*>) :: PromoteResult (a -> b) -> PromoteResult a -> PromoteResult b # liftA2 :: (a -> b -> c) -> PromoteResult a -> PromoteResult b -> PromoteResult c # (*>) :: PromoteResult a -> PromoteResult b -> PromoteResult b # (<*) :: PromoteResult a -> PromoteResult b -> PromoteResult a # | |||||
Functor PromoteResult Source # | |||||
Defined in Cursor.Tree.Promote Methods fmap :: (a -> b) -> PromoteResult a -> PromoteResult b # (<$) :: a -> PromoteResult b -> PromoteResult a # | |||||
Monad PromoteResult Source # | |||||
Defined in Cursor.Tree.Promote Methods (>>=) :: PromoteResult a -> (a -> PromoteResult b) -> PromoteResult b # (>>) :: PromoteResult a -> PromoteResult b -> PromoteResult b # return :: a -> PromoteResult a # | |||||
NFData a => NFData (PromoteResult a) Source # | |||||
Defined in Cursor.Tree.Promote Methods rnf :: PromoteResult a -> () # | |||||
Generic (PromoteResult a) Source # | |||||
Defined in Cursor.Tree.Promote Associated Types
Methods from :: PromoteResult a -> Rep (PromoteResult a) x # to :: Rep (PromoteResult a) x -> PromoteResult a # | |||||
Show a => Show (PromoteResult a) Source # | |||||
Defined in Cursor.Tree.Promote Methods showsPrec :: Int -> PromoteResult a -> ShowS # show :: PromoteResult a -> String # showList :: [PromoteResult a] -> ShowS # | |||||
Eq a => Eq (PromoteResult a) Source # | |||||
Defined in Cursor.Tree.Promote Methods (==) :: PromoteResult a -> PromoteResult a -> Bool # (/=) :: PromoteResult a -> PromoteResult a -> Bool # | |||||
Validity a => Validity (PromoteResult a) Source # | |||||
Defined in Cursor.Tree.Promote Methods validate :: PromoteResult a -> Validation # | |||||
type Rep (PromoteResult a) Source # | |||||
Defined in Cursor.Tree.Promote type Rep (PromoteResult a) = D1 ('MetaData "PromoteResult" "Cursor.Tree.Promote" "cursor-0.3.2.0-DsqeuvBEfePHA4N8n3HFEH" 'False) (C1 ('MetaCons "CannotPromoteTopNode" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "NoGrandparentToPromoteUnder" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Promoted" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))) |
treeCursorDemoteElem :: TreeCursor a -> DemoteResult (TreeCursor a) Source #
treeCursorDemoteSubTree :: TreeCursor a -> DemoteResult (TreeCursor a) Source #
data DemoteResult a Source #
Constructors
CannotDemoteTopNode | |
NoSiblingsToDemoteUnder | |
Demoted a |
Instances
Functor DemoteResult Source # | |||||
Defined in Cursor.Tree.Demote Methods fmap :: (a -> b) -> DemoteResult a -> DemoteResult b # (<$) :: a -> DemoteResult b -> DemoteResult a # | |||||
NFData a => NFData (DemoteResult a) Source # | |||||
Defined in Cursor.Tree.Demote Methods rnf :: DemoteResult a -> () # | |||||
Generic (DemoteResult a) Source # | |||||
Defined in Cursor.Tree.Demote Associated Types
Methods from :: DemoteResult a -> Rep (DemoteResult a) x # to :: Rep (DemoteResult a) x -> DemoteResult a # | |||||
Show a => Show (DemoteResult a) Source # | |||||
Defined in Cursor.Tree.Demote Methods showsPrec :: Int -> DemoteResult a -> ShowS # show :: DemoteResult a -> String # showList :: [DemoteResult a] -> ShowS # | |||||
Eq a => Eq (DemoteResult a) Source # | |||||
Defined in Cursor.Tree.Demote Methods (==) :: DemoteResult a -> DemoteResult a -> Bool # (/=) :: DemoteResult a -> DemoteResult a -> Bool # | |||||
Validity a => Validity (DemoteResult a) Source # | |||||
Defined in Cursor.Tree.Demote Methods validate :: DemoteResult a -> Validation # | |||||
type Rep (DemoteResult a) Source # | |||||
Defined in Cursor.Tree.Demote type Rep (DemoteResult a) = D1 ('MetaData "DemoteResult" "Cursor.Tree.Demote" "cursor-0.3.2.0-DsqeuvBEfePHA4N8n3HFEH" 'False) (C1 ('MetaCons "CannotDemoteTopNode" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "NoSiblingsToDemoteUnder" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Demoted" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))) |
treeCursorDemoteElemUnder :: b -> b -> TreeCursor a b -> Maybe (TreeCursor 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:
p |- a <-- |- b
After:
p |- <given element 1> | |- a <-- |- <given element 2> | |- b
treeCursorDemoteSubTreeUnder :: b -> TreeCursor a b -> TreeCursor 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
Functor CTree Source # | |||||
Foldable CTree Source # | |||||
Defined in Cursor.Tree.Types Methods fold :: Monoid m => CTree m -> m # foldMap :: Monoid m => (a -> m) -> CTree a -> m # foldMap' :: Monoid m => (a -> m) -> CTree a -> m # foldr :: (a -> b -> b) -> b -> CTree a -> b # foldr' :: (a -> b -> b) -> b -> CTree a -> b # foldl :: (b -> a -> b) -> b -> CTree a -> b # foldl' :: (b -> a -> b) -> b -> CTree a -> b # foldr1 :: (a -> a -> a) -> CTree a -> a # foldl1 :: (a -> a -> a) -> CTree a -> a # elem :: Eq a => a -> CTree a -> Bool # maximum :: Ord a => CTree a -> a # minimum :: Ord a => CTree a -> a # | |||||
Traversable CTree Source # | |||||
NFData a => NFData (CTree a) Source # | |||||
Defined in Cursor.Tree.Types | |||||
Generic (CTree a) Source # | |||||
Defined in Cursor.Tree.Types Associated Types
| |||||
Show a => Show (CTree a) Source # | |||||
Eq a => Eq (CTree a) Source # | |||||
Validity a => Validity (CTree a) Source # | |||||
Defined in Cursor.Tree.Types Methods validate :: CTree a -> Validation # | |||||
type Rep (CTree a) Source # | |||||
Defined in Cursor.Tree.Types type Rep (CTree a) = D1 ('MetaData "CTree" "Cursor.Tree.Types" "cursor-0.3.2.0-DsqeuvBEfePHA4N8n3HFEH" 'False) (C1 ('MetaCons "CNode" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (CForest a)))) |
Instances
Functor CForest Source # | |||||
Foldable CForest Source # | |||||
Defined in Cursor.Tree.Types Methods fold :: Monoid m => CForest m -> m # foldMap :: Monoid m => (a -> m) -> CForest a -> m # foldMap' :: Monoid m => (a -> m) -> CForest a -> m # foldr :: (a -> b -> b) -> b -> CForest a -> b # foldr' :: (a -> b -> b) -> b -> CForest a -> b # foldl :: (b -> a -> b) -> b -> CForest a -> b # foldl' :: (b -> a -> b) -> b -> CForest a -> b # foldr1 :: (a -> a -> a) -> CForest a -> a # foldl1 :: (a -> a -> a) -> CForest a -> a # elem :: Eq a => a -> CForest a -> Bool # maximum :: Ord a => CForest a -> a # minimum :: Ord a => CForest a -> a # | |||||
Traversable CForest Source # | |||||
NFData a => NFData (CForest a) Source # | |||||
Defined in Cursor.Tree.Types | |||||
Generic (CForest a) Source # | |||||
Defined in Cursor.Tree.Types Associated Types
| |||||
Show a => Show (CForest a) Source # | |||||
Eq a => Eq (CForest a) Source # | |||||
Validity a => Validity (CForest a) Source # | |||||
Defined in Cursor.Tree.Types Methods validate :: CForest a -> Validation # | |||||
type Rep (CForest a) Source # | |||||
Defined in Cursor.Tree.Types type Rep (CForest a) = D1 ('MetaData "CForest" "Cursor.Tree.Types" "cursor-0.3.2.0-DsqeuvBEfePHA4N8n3HFEH" 'False) (C1 ('MetaCons "EmptyCForest" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ClosedForest" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (NonEmpty (Tree a)))) :+: C1 ('MetaCons "OpenForest" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (NonEmpty (CTree a)))))) |
rebuildCTree :: CTree a -> Tree a Source #