yi-0.6.2.3: The Haskell-Scriptable EditorSource codeContentsIndex
Yi.Syntax.Tree
Description
Generic syntax tree handling functions
Synopsis
class Foldable tree => IsTree tree where
subtrees :: tree t -> [tree t]
uniplate :: tree t -> ([tree t], [tree t] -> tree t)
emptyNode :: tree t
toksAfter :: Foldable t1 => t -> t1 a -> [a]
allToks :: Foldable t => t a -> [a]
tokAtOrBefore :: Foldable t => Point -> t (Tok t1) -> Maybe (Tok t1)
toksInRegion :: Foldable t1 => Region -> t1 (Tok t) -> [Tok t]
sepBy :: Alternative f => f a -> f v -> f [a]
sepBy1 :: Alternative f => f a -> f v -> f [a]
getLastOffset :: Foldable t => t (Tok t1) -> Point
getFirstOffset :: Foldable t => t (Tok t1) -> Point
getFirstElement :: Foldable t => t a -> Maybe a
getLastElement :: Foldable t => t a -> Maybe a
getLastPath :: IsTree tree => [tree (Tok t)] -> Point -> Maybe [tree (Tok t)]
getAllSubTrees :: IsTree tree => tree t -> [tree t]
tokenBasedAnnots :: Foldable t1 => (a1 -> Maybe a) -> t1 a1 -> t -> [a]
tokenBasedStrokes :: Foldable t3 => (a -> b) -> t3 a -> t -> t2 -> t1 -> [b]
subtreeRegion :: Foldable t => t (Tok t1) -> Region
fromLeafToLeafAfter :: IsTree tree => Point -> Node (tree (Tok a)) -> Node (tree (Tok a))
fromNodeToFinal :: IsTree tree => Region -> Node (tree (Tok a)) -> Node (tree (Tok a))
Documentation
class Foldable tree => IsTree tree whereSource
Methods
subtrees :: tree t -> [tree t]Source
Direct subtrees of a tree
uniplate :: tree t -> ([tree t], [tree t] -> tree t)Source
emptyNode :: tree tSource
show/hide Instances
toksAfter :: Foldable t1 => t -> t1 a -> [a]Source
allToks :: Foldable t => t a -> [a]Source
tokAtOrBefore :: Foldable t => Point -> t (Tok t1) -> Maybe (Tok t1)Source
toksInRegion :: Foldable t1 => Region -> t1 (Tok t) -> [Tok t]Source
sepBy :: Alternative f => f a -> f v -> f [a]Source
sepBy1 :: Alternative f => f a -> f v -> f [a]Source
getLastOffset :: Foldable t => t (Tok t1) -> PointSource
getFirstOffset :: Foldable t => t (Tok t1) -> PointSource
getFirstElement :: Foldable t => t a -> Maybe aSource
Return the 1st token of a subtree.
getLastElement :: Foldable t => t a -> Maybe aSource
Return the last token of a subtree.
getLastPath :: IsTree tree => [tree (Tok t)] -> Point -> Maybe [tree (Tok t)]Source
Search the given list, and return the last tree before the given point; with path to the root. (Root is at the start of the path)
getAllSubTrees :: IsTree tree => tree t -> [tree t]Source
Return all subtrees in a tree, in preorder.
tokenBasedAnnots :: Foldable t1 => (a1 -> Maybe a) -> t1 a1 -> t -> [a]Source
tokenBasedStrokes :: Foldable t3 => (a -> b) -> t3 a -> t -> t2 -> t1 -> [b]Source
subtreeRegion :: Foldable t => t (Tok t1) -> RegionSource
fromLeafToLeafAfter :: IsTree tree => Point -> Node (tree (Tok a)) -> Node (tree (Tok a))Source
Search the tree in pre-order starting at a given node, until finding a leaf which is at or after the given point. An effort is also made to return a leaf as close as possible to p. TODO: rename to fromLeafToLeafAt
fromNodeToFinal :: IsTree tree => Region -> Node (tree (Tok a)) -> Node (tree (Tok a))Source
Given an approximate path to a leaf at the end of the region, return: (path to leaf at the end of the region,path from focused node to the leaf, small node encompassing the region)
Produced by Haddock version 2.6.1