cursor-0.3.2.0: Purely Functional Cursors
Safe HaskellNone
LanguageHaskell2010

Cursor.Tree.Types

Contents

Synopsis

Documentation

data TreeCursor a b Source #

Constructors

TreeCursor 

Fields

Instances

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

Defined in Cursor.Tree.Types

Methods

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

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

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

Defined in Cursor.Tree.Types

Methods

showsPrec :: Int -> TreeCursor a b -> ShowS #

show :: TreeCursor a b -> String #

showList :: [TreeCursor a b] -> ShowS #

Generic (TreeCursor a b) Source # 
Instance details

Defined in Cursor.Tree.Types

Associated Types

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

Methods

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

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

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

Defined in Cursor.Tree.Types

Methods

rnf :: TreeCursor a b -> () #

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

Defined in Cursor.Tree.Types

Methods

validate :: TreeCursor a b -> Validation #

type Rep (TreeCursor a b) Source # 
Instance details

Defined in Cursor.Tree.Types

type Rep (TreeCursor a b) = D1 ('MetaData "TreeCursor" "Cursor.Tree.Types" "cursor-0.3.2.0-Ch3lJwc3yY89mrJgbt03T" 'False) (C1 ('MetaCons "TreeCursor" 'PrefixI 'True) (S1 ('MetaSel ('Just "treeAbove") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe (TreeAbove b))) :*: (S1 ('MetaSel ('Just "treeCurrent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Just "treeBelow") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (CForest b)))))

data TreeAbove b Source #

Constructors

TreeAbove 

Instances

Instances details
Functor TreeAbove Source # 
Instance details

Defined in Cursor.Tree.Types

Methods

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

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

Eq b => Eq (TreeAbove b) Source # 
Instance details

Defined in Cursor.Tree.Types

Methods

(==) :: TreeAbove b -> TreeAbove b -> Bool #

(/=) :: TreeAbove b -> TreeAbove b -> Bool #

Show b => Show (TreeAbove b) Source # 
Instance details

Defined in Cursor.Tree.Types

Generic (TreeAbove b) Source # 
Instance details

Defined in Cursor.Tree.Types

Associated Types

type Rep (TreeAbove b) :: Type -> Type #

Methods

from :: TreeAbove b -> Rep (TreeAbove b) x #

to :: Rep (TreeAbove b) x -> TreeAbove b #

NFData b => NFData (TreeAbove b) Source # 
Instance details

Defined in Cursor.Tree.Types

Methods

rnf :: TreeAbove b -> () #

Validity b => Validity (TreeAbove b) Source # 
Instance details

Defined in Cursor.Tree.Types

type Rep (TreeAbove b) Source # 
Instance details

Defined in Cursor.Tree.Types

type Rep (TreeAbove b) = D1 ('MetaData "TreeAbove" "Cursor.Tree.Types" "cursor-0.3.2.0-Ch3lJwc3yY89mrJgbt03T" 'False) (C1 ('MetaCons "TreeAbove" 'PrefixI 'True) ((S1 ('MetaSel ('Just "treeAboveLefts") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [CTree b]) :*: S1 ('MetaSel ('Just "treeAboveAbove") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe (TreeAbove b)))) :*: (S1 ('MetaSel ('Just "treeAboveNode") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b) :*: S1 ('MetaSel ('Just "treeAboveRights") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [CTree b]))))

data TreeCursorSelection Source #

Instances

Instances details
Eq TreeCursorSelection Source # 
Instance details

Defined in Cursor.Tree.Types

Show TreeCursorSelection Source # 
Instance details

Defined in Cursor.Tree.Types

Generic TreeCursorSelection Source # 
Instance details

Defined in Cursor.Tree.Types

Associated Types

type Rep TreeCursorSelection :: Type -> Type #

NFData TreeCursorSelection Source # 
Instance details

Defined in Cursor.Tree.Types

Methods

rnf :: TreeCursorSelection -> () #

Validity TreeCursorSelection Source # 
Instance details

Defined in Cursor.Tree.Types

type Rep TreeCursorSelection Source # 
Instance details

Defined in Cursor.Tree.Types

type Rep TreeCursorSelection = D1 ('MetaData "TreeCursorSelection" "Cursor.Tree.Types" "cursor-0.3.2.0-Ch3lJwc3yY89mrJgbt03T" '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)))

CTree

data CTree a Source #

Constructors

CNode !a (CForest a) 

Instances

Instances details
Functor CTree Source # 
Instance details

Defined in Cursor.Tree.Types

Methods

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

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

Foldable CTree Source # 
Instance details

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 #

toList :: CTree a -> [a] #

null :: CTree a -> Bool #

length :: CTree a -> Int #

elem :: Eq a => a -> CTree a -> Bool #

maximum :: Ord a => CTree a -> a #

minimum :: Ord a => CTree a -> a #

sum :: Num a => CTree a -> a #

product :: Num a => CTree a -> a #

Traversable CTree Source # 
Instance details

Defined in Cursor.Tree.Types

Methods

traverse :: Applicative f => (a -> f b) -> CTree a -> f (CTree b) #

sequenceA :: Applicative f => CTree (f a) -> f (CTree a) #

mapM :: Monad m => (a -> m b) -> CTree a -> m (CTree b) #

sequence :: Monad m => CTree (m a) -> m (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.2.0-Ch3lJwc3yY89mrJgbt03T" '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

Instances details
Functor CForest Source # 
Instance details

Defined in Cursor.Tree.Types

Methods

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

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

Foldable CForest Source # 
Instance details

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 #

toList :: CForest a -> [a] #

null :: CForest a -> Bool #

length :: CForest a -> Int #

elem :: Eq a => a -> CForest a -> Bool #

maximum :: Ord a => CForest a -> a #

minimum :: Ord a => CForest a -> a #

sum :: Num a => CForest a -> a #

product :: Num a => CForest a -> a #

Traversable CForest Source # 
Instance details

Defined in Cursor.Tree.Types

Methods

traverse :: Applicative f => (a -> f b) -> CForest a -> f (CForest b) #

sequenceA :: Applicative f => CForest (f a) -> f (CForest a) #

mapM :: Monad m => (a -> m b) -> CForest a -> m (CForest b) #

sequence :: Monad m => CForest (m a) -> m (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.2.0-Ch3lJwc3yY89mrJgbt03T" '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))))))