cursor-0.3.0.0: Purely Functional Cursors

Safe HaskellNone
LanguageHaskell2010

Cursor.Forest

Synopsis

Documentation

newtype ForestCursor a b Source #

Instances
(Eq b, Eq a) => Eq (ForestCursor a b) Source # 
Instance details

Defined in Cursor.Forest

Methods

(==) :: ForestCursor a b -> ForestCursor a b -> Bool #

(/=) :: ForestCursor a b -> ForestCursor a b -> Bool #

(Show b, Show a) => Show (ForestCursor a b) Source # 
Instance details

Defined in Cursor.Forest

Generic (ForestCursor a b) Source # 
Instance details

Defined in Cursor.Forest

Associated Types

type Rep (ForestCursor a b) :: Type -> Type #

Methods

from :: ForestCursor a b -> Rep (ForestCursor a b) x #

to :: Rep (ForestCursor a b) x -> ForestCursor a b #

(NFData a, NFData b) => NFData (ForestCursor a b) Source # 
Instance details

Defined in Cursor.Forest

Methods

rnf :: ForestCursor a b -> () #

(Validity a, Validity b) => Validity (ForestCursor a b) Source # 
Instance details

Defined in Cursor.Forest

type Rep (ForestCursor a b) Source # 
Instance details

Defined in Cursor.Forest

type Rep (ForestCursor a b) = D1 (MetaData "ForestCursor" "Cursor.Forest" "cursor-0.3.0.0-4Hn80vYAl979Qxk54M4vdL" True) (C1 (MetaCons "ForestCursor" PrefixI True) (S1 (MetaSel (Just "forestCursorListCursor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NonEmptyCursor (TreeCursor a b) (CTree b)))))

mapForestCursor :: (a -> c) -> (b -> d) -> ForestCursor a b -> ForestCursor c d Source #

forestCursorSelectLastTreeCursor :: (a -> b) -> (b -> a) -> ForestCursor a b -> ForestCursor a b Source #

forestCursorSelectPrev :: (a -> b) -> (b -> a) -> ForestCursor a b -> Maybe (ForestCursor a b) Source #

forestCursorSelectNext :: (a -> b) -> (b -> a) -> ForestCursor a b -> Maybe (ForestCursor a b) Source #

forestCursorSelectFirst :: (a -> b) -> (b -> a) -> ForestCursor a b -> ForestCursor a b Source #

forestCursorSelectLast :: (a -> b) -> (b -> a) -> ForestCursor a b -> ForestCursor a b Source #

forestCursorSelectAbove :: (a -> b) -> (b -> a) -> ForestCursor a b -> Maybe (ForestCursor a b) Source #

forestCursorSelectBelowAtPos :: (a -> b) -> (b -> a) -> Int -> ForestCursor a b -> Maybe (ForestCursor a b) Source #

forestCursorSelectBelowAtStart :: (a -> b) -> (b -> a) -> ForestCursor a b -> Maybe (ForestCursor a b) Source #

forestCursorSelectBelowAtEnd :: (a -> b) -> (b -> a) -> ForestCursor a b -> Maybe (ForestCursor a b) Source #

forestCursorSelectIndex :: (a -> b) -> (b -> a) -> Int -> ForestCursor a b -> Maybe (ForestCursor a b) Source #

forestCursorInsertAndSelectTree :: (a -> b) -> (b -> a) -> Tree b -> ForestCursor a b -> ForestCursor a b Source #

forestCursorAppendAndSelectTree :: (a -> b) -> (b -> a) -> Tree b -> ForestCursor a b -> ForestCursor a b Source #

forestCursorInsertAndSelect :: (a -> b) -> (b -> a) -> b -> ForestCursor a b -> ForestCursor a b Source #

forestCursorAppendAndSelect :: (a -> b) -> (b -> a) -> b -> ForestCursor a b -> ForestCursor a b Source #

forestCursorAddRoot :: (a -> b) -> (b -> a) -> ForestCursor a b -> a -> TreeCursor a b 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 :: (a -> b) -> (b -> a) -> ForestCursor a b -> Maybe (ForestCursor a b) Source #

Promotes the current node to the level of its parent.

Example:

Before:

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

After:

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

forestCursorPromoteSubTree :: (a -> b) -> (b -> a) -> ForestCursor a b -> Maybe (ForestCursor a b) Source #

Promotes the current node to the level of its parent.

Example:

Before:

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

After:

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

forestCursorDemoteElem :: (a -> b) -> (b -> a) -> ForestCursor a b -> Maybe (ForestCursor a b) Source #

Demotes the current node to the level of its children.

Example:

Before:

- a
  |- b
- c <--
  |- d
- e

After:

- a
  |- b
  |- c <--
  |- d
- e

forestCursorDemoteSubTree :: (a -> b) -> (b -> a) -> ForestCursor a b -> Maybe (ForestCursor a b) Source #

Demotes the current subtree to the level of its children.

Example:

Before:

 - a
   |- b
 - c <--
   |- d

After:

 - a
   |- b
   |- c <--
      |- d

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

data CTree a Source #

Constructors

CNode !a (CForest a) 
Instances
Functor CTree Source # 
Instance details

Defined in Cursor.Tree.Types

Methods

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

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

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

Defined in Cursor.Tree.Types

Methods

(==) :: CTree a -> CTree a -> Bool #

(/=) :: CTree a -> CTree a -> Bool #

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

Defined in Cursor.Tree.Types

Methods

showsPrec :: Int -> CTree a -> ShowS #

show :: CTree a -> String #

showList :: [CTree a] -> ShowS #

Generic (CTree a) Source # 
Instance details

Defined in Cursor.Tree.Types

Associated Types

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

Methods

from :: CTree a -> Rep (CTree a) x #

to :: Rep (CTree a) x -> CTree a #

NFData a => NFData (CTree a) Source # 
Instance details

Defined in Cursor.Tree.Types

Methods

rnf :: CTree a -> () #

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

Defined in Cursor.Tree.Types

Methods

validate :: CTree a -> Validation #

type Rep (CTree a) Source # 
Instance details

Defined in Cursor.Tree.Types

type Rep (CTree a) = D1 (MetaData "CTree" "Cursor.Tree.Types" "cursor-0.3.0.0-4Hn80vYAl979Qxk54M4vdL" 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))))

cTree :: Bool -> Tree a -> CTree a Source #

data CForest a Source #

Instances
Functor CForest Source # 
Instance details

Defined in Cursor.Tree.Types

Methods

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

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

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

Defined in Cursor.Tree.Types

Methods

(==) :: CForest a -> CForest a -> Bool #

(/=) :: CForest a -> CForest a -> Bool #

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

Defined in Cursor.Tree.Types

Methods

showsPrec :: Int -> CForest a -> ShowS #

show :: CForest a -> String #

showList :: [CForest a] -> ShowS #

Generic (CForest a) Source # 
Instance details

Defined in Cursor.Tree.Types

Associated Types

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

Methods

from :: CForest a -> Rep (CForest a) x #

to :: Rep (CForest a) x -> CForest a #

NFData a => NFData (CForest a) Source # 
Instance details

Defined in Cursor.Tree.Types

Methods

rnf :: CForest a -> () #

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

Defined in Cursor.Tree.Types

Methods

validate :: CForest a -> Validation #

type Rep (CForest a) Source # 
Instance details

Defined in Cursor.Tree.Types

type Rep (CForest a) = D1 (MetaData "CForest" "Cursor.Tree.Types" "cursor-0.3.0.0-4Hn80vYAl979Qxk54M4vdL" 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))))))

traverseForestCursor :: ([CTree b] -> TreeCursor a b -> [CTree b] -> f c) -> ForestCursor a b -> f c Source #

foldForestCursor :: ([CTree b] -> TreeCursor a b -> [CTree b] -> c) -> ForestCursor a b -> c Source #