X-0.3.1.0: A light-weight XML library

Copyright(c) Galois Inc. 2008
(c) Herbert Valerio Riedel 2019
LicenseBSD-3-Clause AND GPL-3.0-or-later
Safe HaskellSafe
LanguageHaskell2010

Text.XML.Cursor

Contents

Description

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

Documentation

data Tag Source #

Constructors

Tag 

Fields

Instances
Data Tag Source # 
Instance details

Defined in Text.XML.Cursor

Methods

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 #

toConstr :: Tag -> Constr #

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 # 
Instance details

Defined in Text.XML.Cursor

Methods

showsPrec :: Int -> Tag -> ShowS #

show :: Tag -> String #

showList :: [Tag] -> ShowS #

Generic Tag Source # 
Instance details

Defined in Text.XML.Cursor

Associated Types

type Rep Tag :: Type -> Type #

Methods

from :: Tag -> Rep Tag x #

to :: Rep Tag x -> Tag #

NFData Tag Source # 
Instance details

Defined in Text.XML.Cursor

Methods

rnf :: Tag -> () #

type Rep Tag Source # 
Instance details

Defined in Text.XML.Cursor

type Rep Tag = D1 (MetaData "Tag" "Text.XML.Cursor" "X-0.3.1.0-FtMev6r53LM7jz5ldGnRwK" False) (C1 (MetaCons "Tag" PrefixI True) (S1 (MetaSel (Just "tagName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 QName) :*: S1 (MetaSel (Just "tagAttribs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Attr])))

type Cursor = Cursor' Content Source #

General cursor

data Cursor' content Source #

The position of a piece of content in an XML document.

Since: 0.3.0

Constructors

Cur 

Fields

  • current :: content

    The currently selected content.

  • lefts :: [Content]

    Siblings on the left, closest first.

  • rights :: [Content]

    Siblings on the right, closest first.

  • parents :: Path

    The contexts of the parent elements of this location.

Instances
Functor Cursor' Source # 
Instance details

Defined in Text.XML.Cursor

Methods

fmap :: (a -> b) -> Cursor' a -> Cursor' b #

(<$) :: a -> Cursor' b -> Cursor' a #

Foldable Cursor' Source # 
Instance details

Defined in Text.XML.Cursor

Methods

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 #

toList :: Cursor' a -> [a] #

null :: Cursor' a -> Bool #

length :: Cursor' a -> Int #

elem :: Eq a => a -> Cursor' a -> Bool #

maximum :: Ord a => Cursor' a -> a #

minimum :: Ord a => Cursor' a -> a #

sum :: Num a => Cursor' a -> a #

product :: Num a => Cursor' a -> a #

Traversable Cursor' Source # 
Instance details

Defined in Text.XML.Cursor

Methods

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

sequenceA :: Applicative f => Cursor' (f a) -> f (Cursor' a) #

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

sequence :: Monad m => Cursor' (m a) -> m (Cursor' a) #

Data content => Data (Cursor' content) Source # 
Instance details

Defined in Text.XML.Cursor

Methods

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 # 
Instance details

Defined in Text.XML.Cursor

Methods

showsPrec :: Int -> Cursor' content -> ShowS #

show :: Cursor' content -> String #

showList :: [Cursor' content] -> ShowS #

Generic (Cursor' content) Source # 
Instance details

Defined in Text.XML.Cursor

Associated Types

type Rep (Cursor' content) :: Type -> Type #

Methods

from :: Cursor' content -> Rep (Cursor' content) x #

to :: Rep (Cursor' content) x -> Cursor' content #

NFData content => NFData (Cursor' content) Source # 
Instance details

Defined in Text.XML.Cursor

Methods

rnf :: Cursor' content -> () #

type Rep (Cursor' content) Source # 
Instance details

Defined in Text.XML.Cursor

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

fromRoot :: Root -> Cursor' Element Source #

Construct cursor from document Root

Since: 0.3.0

toRootElement :: IsContent content => Cursor' content -> Element Source #

Computes the root element containing this location.

NOTE: The root element might have siblings; see toRoot or root if you need to deal with such siblings.

Since: 0.3.0

toRoot :: IsContent content => Cursor' content -> Maybe Root Source #

Constructs the document Root containing this location.

Returns Nothing if invalid top-level "miscellaneous" nodes are encountered.

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 :: IsContent content => (Cursor -> Bool) -> Cursor' content -> Maybe Cursor Source #

The first child that satisfies a predicate.

findLeft :: IsContent content => (Cursor -> Bool) -> Cursor' content -> Maybe Cursor Source #

Find the next left sibling that satisfies a predicate.

findRight :: IsContent content => (Cursor -> Bool) -> Cursor' content -> Maybe Cursor Source #

Find the next right sibling that satisfies a predicate.

findRec :: IsContent content => (Cursor -> Bool) -> Cursor' content -> Maybe Cursor Source #

Perform a depth first search for a descendant that satisfies the given predicate.

Node classification

isRoot :: Cursor' content -> Bool Source #

Are we at the top of the document?

isFirst :: Cursor' content -> Bool Source #

Are we at the left end of the the document (i.e. the locally left-most sibling)?

isLast :: Cursor' content -> Bool Source #

Are we at the right end of the document (i.e. the locally right-most sibling)?

isLeaf :: IsContent content => Cursor' content -> Bool Source #

Are we at the bottom of the document?

isChild :: Cursor' content -> Bool Source #

Do we have a parent?

hasChildren :: IsContent content => Cursor' content -> Bool Source #

Do we have children?

getNodeIndex :: Cursor' content -> Word Source #

Get the node index inside the sequence of children/siblings

Inserting content

insertLeft :: IsContent c => c -> Cursor' content -> Cursor' content Source #

Insert content to the left of the current position.

insertRight :: IsContent c => c -> Cursor' content -> Cursor' content Source #

Insert content to the right of the current position.

insertGoLeft :: IsContent content2 => content -> Cursor' content2 -> Cursor' content Source #

Insert content to the left of the current position. The new content becomes the current position.

insertGoRight :: IsContent content2 => content -> Cursor' content2 -> Cursor' content Source #

Insert content to the right of the current position. The new content becomes the current position.

Removing content

removeLeft :: Cursor' content -> Maybe (Content, Cursor' content) Source #

Remove the content on the left of the current position, if any.

removeRight :: Cursor' content -> Maybe (Content, Cursor' content) 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.

removeGoRight :: Cursor' content -> Maybe Cursor Source #

Remove the current element. The new position is the one on the right.

removeGoUp :: Cursor' content -> Maybe Cursor Source #

Remove the current element. The new position is the parent of the old position.