chiasma-0.10.1.0: A tmux client for Polysemy
Safe HaskellSafe-Inferred
LanguageGHC2021

Chiasma.Lens.Tree

Documentation

newtype NodeIndexTree l p Source #

Constructors

NodeIndexTree 

Fields

Instances

Instances details
(Show l, Show p) => Show (NodeIndexTree l p) Source # 
Instance details

Defined in Chiasma.Lens.Tree

(Eq l, Eq p) => Eq (NodeIndexTree l p) Source # 
Instance details

Defined in Chiasma.Lens.Tree

Methods

(==) :: NodeIndexTree l p -> NodeIndexTree l p -> Bool #

(/=) :: NodeIndexTree l p -> NodeIndexTree l p -> Bool #

Identifiable l => Ixed (NodeIndexTree l p) Source # 
Instance details

Defined in Chiasma.Lens.Tree

(Data l, Data p) => Plated (NodeIndexTree l p) Source # 
Instance details

Defined in Chiasma.Lens.Tree

HasNodeIndexTree (NodeIndexTree l p) l p Source # 
Instance details

Defined in Chiasma.Lens.Tree

type Index (NodeIndexTree _1 _2) Source # 
Instance details

Defined in Chiasma.Lens.Tree

type Index (NodeIndexTree _1 _2) = Ident
type IxValue (NodeIndexTree l _1) Source # 
Instance details

Defined in Chiasma.Lens.Tree

type IxValue (NodeIndexTree l _1) = l

class HasNodeIndexTree c l p | c -> l p where Source #

Minimal complete definition

nodeIndexTree

Instances

Instances details
HasNodeIndexTree (NodeIndexTree l p) l p Source # 
Instance details

Defined in Chiasma.Lens.Tree

newtype LeafIndexTree l p Source #

Constructors

LeafIndexTree 

Fields

Instances

Instances details
(Show l, Show p) => Show (LeafIndexTree l p) Source # 
Instance details

Defined in Chiasma.Lens.Tree

(Eq l, Eq p) => Eq (LeafIndexTree l p) Source # 
Instance details

Defined in Chiasma.Lens.Tree

Methods

(==) :: LeafIndexTree l p -> LeafIndexTree l p -> Bool #

(/=) :: LeafIndexTree l p -> LeafIndexTree l p -> Bool #

Identifiable p => Ixed (LeafIndexTree l p) Source # 
Instance details

Defined in Chiasma.Lens.Tree

(Data l, Data p) => Plated (LeafIndexTree l p) Source # 
Instance details

Defined in Chiasma.Lens.Tree

HasLeafIndexTree (LeafIndexTree l p) l p Source # 
Instance details

Defined in Chiasma.Lens.Tree

type Index (LeafIndexTree _1 _2) Source # 
Instance details

Defined in Chiasma.Lens.Tree

type Index (LeafIndexTree _1 _2) = Ident
type IxValue (LeafIndexTree _1 p) Source # 
Instance details

Defined in Chiasma.Lens.Tree

type IxValue (LeafIndexTree _1 p) = p

class HasLeafIndexTree c l p | c -> l p where Source #

Minimal complete definition

leafIndexTree

Instances

Instances details
HasLeafIndexTree (LeafIndexTree l p) l p Source # 
Instance details

Defined in Chiasma.Lens.Tree

plateWrap :: (Data l, Data p) => (Tree l p -> t l p) -> (t l p -> Tree l p) -> Traversal' (t l p) (t l p) Source #

nodesIdent :: forall l p. Identifiable l => Data l => Data p => Ident -> Fold (Tree l p) l Source #

nodeByIdent :: forall l p. Identifiable l => Data l => Data p => Ident -> Tree l p -> Maybe l Source #

nodesByIdent :: forall l p. Identifiable l => Data l => Data p => Ident -> Tree l p -> [l] Source #

leavesByIdentRecursive :: forall l p. Identifiable p => Data l => Data p => Ident -> Fold (LeafIndexTree l p) p Source #

leavesIdent :: forall l p. Identifiable p => Data l => Data p => Ident -> Fold (Tree l p) p Source #

leafByIdent :: forall l p. Identifiable p => Data l => Data p => Ident -> Tree l p -> Maybe p Source #

leavesByIdent :: forall l p. Identifiable p => Data l => Data p => Ident -> Tree l p -> [p] Source #

modifyLeafByIdent :: (Identifiable p, Data l, Data p) => Ident -> (p -> p) -> Tree l p -> Tree l p Source #

subtreesWithLayout :: forall l p m. Monad m => ((l, TreeSub l p) -> m (l, TreeSub l p)) -> Tree l p -> m (Tree l p) Source #

subtrees :: forall l p m. Monad m => (TreeSub l p -> m (TreeSub l p)) -> Tree l p -> m (Tree l p) Source #

treesAndSubs :: Monad m => (Tree l p -> m (Tree l p)) -> (TreeSub l p -> m (TreeSub l p)) -> Tree l p -> m (Tree l p) Source #