Copyright | (c) Galois Inc. 2008 (c) Herbert Valerio Riedel 2019 |
---|---|
License | BSD-3-Clause AND GPL-3.0-or-later |
Safe Haskell | None |
Language | Haskell2010 |
XML cursors for working XML content withing the context of an XML document. This implementation is based on the general tree zipper written by Krasimir Angelov and Iavor S. Diatchki.
NOTE: The Cursor API has been significantly altered in 0.3.0, hence this module's API is to be considered "since 0.3.0"
Since: 0.3.0
Synopsis
- data Tag = Tag {
- tagName :: QName
- tagAttribs :: [Attr]
- getTag :: Element -> Tag
- setTag :: Tag -> Element -> Element
- fromTag :: Tag -> [Content] -> Element
- type Cursor = Cursor' Content
- data Cursor' content = Cur {}
- type Path = [([Content], Tag, [Content])]
- fromRootElement :: Element -> Cursor' Element
- fromRoot :: Root -> Cursor' Element
- toRootElement :: IsContent content => Cursor' content -> Element
- toRoot :: IsContent content => Cursor' content -> Maybe Root
- upCast :: IsContent content => Cursor' content -> Cursor
- downCast :: IsContent content => Cursor -> Maybe (Cursor' content)
- parent :: IsContent content => Cursor' content -> Maybe (Cursor' Element)
- root :: IsContent content => Cursor' content -> Cursor' Element
- getChild :: IsContent content => Word -> Cursor' content -> Maybe Cursor
- firstChild :: IsContent content => Cursor' content -> Maybe Cursor
- lastChild :: IsContent content => Cursor' content -> Maybe Cursor
- left :: IsContent content => Cursor' content -> Maybe Cursor
- right :: IsContent content => Cursor' content -> Maybe Cursor
- nextDF :: IsContent content => Cursor' content -> Maybe Cursor
- findChild :: (Cursor -> Bool) -> Cursor -> Maybe Cursor
- findLeft :: (Cursor -> Bool) -> Cursor -> Maybe Cursor
- findRight :: (Cursor -> Bool) -> Cursor -> Maybe Cursor
- findRec :: (Cursor -> Bool) -> Cursor -> Maybe Cursor
- isRoot :: Cursor' content -> Bool
- isFirst :: Cursor' content -> Bool
- isLast :: Cursor' content -> Bool
- isLeaf :: IsContent content => Cursor' content -> Bool
- isChild :: Cursor' content -> Bool
- hasChildren :: IsContent content => Cursor' content -> Bool
- getNodeIndex :: Cursor' content -> Word
- insertLeft :: IsContent c => c -> Cursor' content -> Cursor' content
- insertRight :: Content -> Cursor' content -> Cursor' content
- insertGoLeft :: Content -> Cursor -> Cursor
- insertGoRight :: Content -> Cursor -> Cursor
- removeLeft :: Cursor -> Maybe (Content, Cursor)
- removeRight :: Cursor -> Maybe (Content, Cursor)
- removeGoLeft :: Cursor' content -> Maybe Cursor
- removeGoRight :: Cursor' content -> Maybe Cursor
- removeGoUp :: Cursor' content -> Maybe Cursor
Documentation
Tag | |
|
Instances
Data Tag Source # | |
Defined in Text.XML.Cursor gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Tag -> c Tag # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Tag # dataTypeOf :: Tag -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Tag) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Tag) # gmapT :: (forall b. Data b => b -> b) -> Tag -> Tag # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Tag -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Tag -> r # gmapQ :: (forall d. Data d => d -> u) -> Tag -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Tag -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Tag -> m Tag # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Tag -> m Tag # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Tag -> m Tag # | |
Show Tag Source # | |
Generic Tag Source # | |
NFData Tag Source # | |
Defined in Text.XML.Cursor | |
type Rep Tag Source # | |
Defined in Text.XML.Cursor type Rep Tag = D1 (MetaData "Tag" "Text.XML.Cursor" "X-0.3.0.0-inplace" False) (C1 (MetaCons "Tag" PrefixI True) (S1 (MetaSel (Just "tagName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 QName) :*: S1 (MetaSel (Just "tagAttribs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Attr]))) |
The position of a piece of content in an XML document.
Since: 0.3.0
Instances
Functor Cursor' Source # | |
Foldable Cursor' Source # | |
Defined in Text.XML.Cursor fold :: Monoid m => Cursor' m -> m # foldMap :: Monoid m => (a -> m) -> Cursor' a -> m # foldr :: (a -> b -> b) -> b -> Cursor' a -> b # foldr' :: (a -> b -> b) -> b -> Cursor' a -> b # foldl :: (b -> a -> b) -> b -> Cursor' a -> b # foldl' :: (b -> a -> b) -> b -> Cursor' a -> b # foldr1 :: (a -> a -> a) -> Cursor' a -> a # foldl1 :: (a -> a -> a) -> Cursor' a -> a # elem :: Eq a => a -> Cursor' a -> Bool # maximum :: Ord a => Cursor' a -> a # minimum :: Ord a => Cursor' a -> a # | |
Traversable Cursor' Source # | |
Data content => Data (Cursor' content) Source # | |
Defined in Text.XML.Cursor gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Cursor' content -> c (Cursor' content) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Cursor' content) # toConstr :: Cursor' content -> Constr # dataTypeOf :: Cursor' content -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Cursor' content)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Cursor' content)) # gmapT :: (forall b. Data b => b -> b) -> Cursor' content -> Cursor' content # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Cursor' content -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Cursor' content -> r # gmapQ :: (forall d. Data d => d -> u) -> Cursor' content -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Cursor' content -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Cursor' content -> m (Cursor' content) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Cursor' content -> m (Cursor' content) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Cursor' content -> m (Cursor' content) # | |
Show content => Show (Cursor' content) Source # | |
Generic (Cursor' content) Source # | |
NFData content => NFData (Cursor' content) Source # | |
Defined in Text.XML.Cursor | |
type Rep (Cursor' content) Source # | |
Defined in Text.XML.Cursor type Rep (Cursor' content) = D1 (MetaData "Cursor'" "Text.XML.Cursor" "X-0.3.0.0-inplace" False) (C1 (MetaCons "Cur" PrefixI True) ((S1 (MetaSel (Just "current") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 content) :*: S1 (MetaSel (Just "lefts") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Content])) :*: (S1 (MetaSel (Just "rights") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Content]) :*: S1 (MetaSel (Just "parents") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Path)))) |
type Path = [([Content], Tag, [Content])] Source #
Parent path (with the root as last element) consisting of list of left siblings, parent, and right siblings
Conversions
fromRootElement :: Element -> Cursor' Element Source #
A cursor for the given (root) element.
Since: 0.3.0
upCast :: IsContent content => Cursor' content -> Cursor Source #
Generalize content type of current Cursor
location
Since: 0.3.0
downCast :: IsContent content => Cursor -> Maybe (Cursor' content) Source #
Specialize content type of current Cursor
location
Since: 0.3.0
Moving around
parent :: IsContent content => Cursor' content -> Maybe (Cursor' Element) Source #
The parent of the given location.
root :: IsContent content => Cursor' content -> Cursor' Element Source #
The top-most parent of the given location.
getChild :: IsContent content => Word -> Cursor' content -> Maybe Cursor Source #
The child with the given index (starting from 0).
firstChild :: IsContent content => Cursor' content -> Maybe Cursor Source #
The first child of the given location.
lastChild :: IsContent content => Cursor' content -> Maybe Cursor Source #
The last child of the given location.
left :: IsContent content => Cursor' content -> Maybe Cursor Source #
The left sibling of the given location.
right :: IsContent content => Cursor' content -> Maybe Cursor Source #
The right sibling of the given location.
nextDF :: IsContent content => Cursor' content -> Maybe Cursor Source #
The next position in a left-to-right depth-first traversal of a document: either the first child, right sibling, or the right sibling of a parent that has one.
Searching
findChild :: (Cursor -> Bool) -> Cursor -> Maybe Cursor Source #
The first child that satisfies a predicate.
findLeft :: (Cursor -> Bool) -> Cursor -> Maybe Cursor Source #
Find the next left sibling that satisfies a predicate.
findRight :: (Cursor -> Bool) -> Cursor -> Maybe Cursor Source #
Find the next right sibling that satisfies a predicate.
findRec :: (Cursor -> Bool) -> Cursor -> Maybe Cursor Source #
Perform a depth first search for a descendant that satisfies the given predicate.
Node classification
isLeaf :: IsContent content => Cursor' content -> Bool Source #
Are we at the bottom of the document?
getNodeIndex :: Cursor' content -> Word Source #
Get the node index inside the sequence of children
Inserting content
insertLeft :: IsContent c => c -> Cursor' content -> Cursor' content Source #
Insert content to the left of the current position.
insertRight :: Content -> Cursor' content -> Cursor' content Source #
Insert content to the right of the current position.
insertGoLeft :: Content -> Cursor -> Cursor Source #
Insert content to the left of the current position. The new content becomes the current position.
insertGoRight :: Content -> Cursor -> Cursor Source #
Insert content to the right of the current position. The new content becomes the current position.
Removing content
removeLeft :: Cursor -> Maybe (Content, Cursor) Source #
Remove the content on the left of the current position, if any.
removeRight :: Cursor -> Maybe (Content, Cursor) Source #
Remove the content on the right of the current position, if any.
removeGoLeft :: Cursor' content -> Maybe Cursor Source #
Remove the current element. The new position is the one on the left.