cursor-0.1.0.0: Purely Functional Cursors

Safe HaskellNone
LanguageHaskell2010

Cursor.Tree.Promote

Synopsis

Documentation

treeCursorPromoteElem :: (a -> b) -> (b -> a) -> TreeCursor a b -> PromoteElemResult (TreeCursor a b) Source #

Promotes the current node to the level of its parent.

Example:

Before:

 p
 |- a
 |  |- b
 |  |  |- c
 |  |- d <--
 |  |  |- e
 |  |- f
 |     |- g
 |- h

After:

 p
 |- a
 |  |- b
 |  |  |- c
 |  |  |- e
 |  |- f
 |     |- g
 |- d <--
 |- h

data PromoteElemResult a Source #

Instances
Monad PromoteElemResult Source # 
Instance details

Defined in Cursor.Tree.Promote

Functor PromoteElemResult Source # 
Instance details

Defined in Cursor.Tree.Promote

Applicative PromoteElemResult Source # 
Instance details

Defined in Cursor.Tree.Promote

Eq a => Eq (PromoteElemResult a) Source # 
Instance details

Defined in Cursor.Tree.Promote

Show a => Show (PromoteElemResult a) Source # 
Instance details

Defined in Cursor.Tree.Promote

Generic (PromoteElemResult a) Source # 
Instance details

Defined in Cursor.Tree.Promote

Associated Types

type Rep (PromoteElemResult a) :: Type -> Type #

Validity a => Validity (PromoteElemResult a) Source # 
Instance details

Defined in Cursor.Tree.Promote

type Rep (PromoteElemResult a) Source # 
Instance details

Defined in Cursor.Tree.Promote

type Rep (PromoteElemResult a) = D1 (MetaData "PromoteElemResult" "Cursor.Tree.Promote" "cursor-0.1.0.0-Iybup7BIS90EqxmhE2JMA0" 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 :: (a -> b) -> (b -> a) -> TreeCursor a b -> PromoteResult (TreeCursor a b) Source #

Promotes the current node to the level of its parent.

Example:

Before:

 p
 |- a
 |  |- b
 |  |  |- c
 |  |- d <--
 |  |  |- e
 |  |- f
 |     |- g
 |- h

After:

 p
 |- a
 |  |- b
 |  |  |- c
 |  |- f
 |     |- g
 |- d <--
 |  |- e
 |- h

data PromoteResult a Source #

Instances
Monad PromoteResult Source # 
Instance details

Defined in Cursor.Tree.Promote

Functor PromoteResult Source # 
Instance details

Defined in Cursor.Tree.Promote

Methods

fmap :: (a -> b) -> PromoteResult a -> PromoteResult b #

(<$) :: a -> PromoteResult b -> PromoteResult a #

Applicative PromoteResult Source # 
Instance details

Defined in Cursor.Tree.Promote

Eq a => Eq (PromoteResult a) Source # 
Instance details

Defined in Cursor.Tree.Promote

Show a => Show (PromoteResult a) Source # 
Instance details

Defined in Cursor.Tree.Promote

Generic (PromoteResult a) Source # 
Instance details

Defined in Cursor.Tree.Promote

Associated Types

type Rep (PromoteResult a) :: Type -> Type #

Validity a => Validity (PromoteResult a) Source # 
Instance details

Defined in Cursor.Tree.Promote

type Rep (PromoteResult a) Source # 
Instance details

Defined in Cursor.Tree.Promote

type Rep (PromoteResult a) = D1 (MetaData "PromoteResult" "Cursor.Tree.Promote" "cursor-0.1.0.0-Iybup7BIS90EqxmhE2JMA0" 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))))