hexpat-0.20.12: XML parser/formatter based on expat

Safe HaskellNone
LanguageHaskell98

Text.XML.Expat.Internal.NodeClass

Description

Type classes to allow for XML handling functions to be generalized to work with different node types, including the ones defined in Tree and Annotated.

Synopsis

Documentation

type Attributes tag text = [(tag, text)] Source #

Type shortcut for attributes

type UAttributes text = Attributes text text Source #

Type shortcut for attributes with unqualified names where tag and text are the same string type.

textContent :: (NodeClass n [], Monoid text) => n [] tag text -> text Source #

Extract all text content from inside a tag into a single string, including any text contained in children. This excludes the contents of comments or processing instructions. To get the text for these node types, use getText.

type family ListOf n Source #

A type function to give the type of a list of nodes, using the appropriate list type for the specified node type, e.g. ListOf (UNode Text)

Instances

type ListOf (NodeG c tag text) Source # 
type ListOf (NodeG c tag text) = c (NodeG c tag text)
type ListOf (NodeG a c tag text) Source # 
type ListOf (NodeG a c tag text) = c (NodeG a c tag text)
type ListOf (NodeG a c tag text) Source # 
type ListOf (NodeG a c tag text) = c (NodeG a c tag text)

class (Functor c, List c) => NodeClass n c where Source #

Methods

isElement :: n c tag text -> Bool Source #

Is the given node an element?

isText :: n c tag text -> Bool Source #

Is the given node text?

isCData :: n c tag text -> Bool Source #

Is the given node CData?

isProcessingInstruction :: n c tag text -> Bool Source #

Is the given node a processing instruction?

isComment :: n c tag text -> Bool Source #

Is the given node a comment?

textContentM :: Monoid text => n c tag text -> ItemM c text Source #

Extract all text content from inside a tag into a single string, including any text contained in children. This excludes the contents of comments or processing instructions. To get the text for these node types, use getText.

isNamed :: Eq tag => tag -> n c tag text -> Bool Source #

Is the given node a tag with the given name?

getName :: Monoid tag => n c tag text -> tag Source #

Get the name of this node if it's an element, return empty string otherwise.

hasTarget :: Eq text => text -> n c tag text -> Bool Source #

Is the given node a Processing Instruction with the given target?

getTarget :: Monoid text => n c tag text -> text Source #

Get the target of this node if it's a Processing Instruction, return empty string otherwise.

getAttributes :: n c tag text -> [(tag, text)] Source #

Get the attributes of a node if it's an element, return empty list otherwise.

getChildren :: n c tag text -> c (n c tag text) Source #

Get children of a node if it's an element, return empty list otherwise.

getText :: Monoid text => n c tag text -> text Source #

Get this node's text if it's a text node, comment, or processing instruction, return empty text otherwise.

modifyName :: (tag -> tag) -> n c tag text -> n c tag text Source #

Modify name if it's an element, no-op otherwise.

modifyAttributes :: ([(tag, text)] -> [(tag, text)]) -> n c tag text -> n c tag text Source #

Modify attributes if it's an element, no-op otherwise.

modifyChildren :: (c (n c tag text) -> c (n c tag text)) -> n c tag text -> n c tag text Source #

Modify children (non-recursively) if it's an element, no-op otherwise.

modifyElement :: ((tag, [(tag, text)], c (n c tag text)) -> (tag', [(tag', text)], c (n c tag' text))) -> n c tag text -> n c tag' text Source #

Map an element non-recursively, allowing the tag type to be changed.

mapAllTags :: (tag -> tag') -> n c tag text -> n c tag' text Source #

Map all tags (both tag names and attribute names) recursively.

mapNodeContainer :: List c' => (forall a. c a -> ItemM c (c' a)) -> n c tag text -> ItemM c (n c' tag text) Source #

Change a node recursively from one container type to another, with a specified function to convert the container type.

mkText :: text -> n c tag text Source #

Generic text node constructor.

Instances

(Functor c, List c) => NodeClass NodeG c Source # 

Methods

isElement :: NodeG c tag text -> Bool Source #

isText :: NodeG c tag text -> Bool Source #

isCData :: NodeG c tag text -> Bool Source #

isProcessingInstruction :: NodeG c tag text -> Bool Source #

isComment :: NodeG c tag text -> Bool Source #

textContentM :: Monoid text => NodeG c tag text -> ItemM c text Source #

isNamed :: Eq tag => tag -> NodeG c tag text -> Bool Source #

getName :: Monoid tag => NodeG c tag text -> tag Source #

hasTarget :: Eq text => text -> NodeG c tag text -> Bool Source #

getTarget :: Monoid text => NodeG c tag text -> text Source #

getAttributes :: NodeG c tag text -> [(tag, text)] Source #

getChildren :: NodeG c tag text -> c (NodeG c tag text) Source #

getText :: Monoid text => NodeG c tag text -> text Source #

modifyName :: (tag -> tag) -> NodeG c tag text -> NodeG c tag text Source #

modifyAttributes :: ([(tag, text)] -> [(tag, text)]) -> NodeG c tag text -> NodeG c tag text Source #

modifyChildren :: (c (NodeG c tag text) -> c (NodeG c tag text)) -> NodeG c tag text -> NodeG c tag text Source #

modifyElement :: ((tag, [(tag, text)], c (NodeG c tag text)) -> (tag', [(tag', text)], c (NodeG c tag' text))) -> NodeG c tag text -> NodeG c tag' text Source #

mapAllTags :: (tag -> tag') -> NodeG c tag text -> NodeG c tag' text Source #

mapNodeContainer :: List c' => (forall a. c a -> ItemM c (c' a)) -> NodeG c tag text -> ItemM c (NodeG c' tag text) Source #

mkText :: text -> NodeG c tag text Source #

(Functor c, List c) => NodeClass (NodeG a) c Source # 

Methods

isElement :: NodeG a c tag text -> Bool Source #

isText :: NodeG a c tag text -> Bool Source #

isCData :: NodeG a c tag text -> Bool Source #

isProcessingInstruction :: NodeG a c tag text -> Bool Source #

isComment :: NodeG a c tag text -> Bool Source #

textContentM :: Monoid text => NodeG a c tag text -> ItemM c text Source #

isNamed :: Eq tag => tag -> NodeG a c tag text -> Bool Source #

getName :: Monoid tag => NodeG a c tag text -> tag Source #

hasTarget :: Eq text => text -> NodeG a c tag text -> Bool Source #

getTarget :: Monoid text => NodeG a c tag text -> text Source #

getAttributes :: NodeG a c tag text -> [(tag, text)] Source #

getChildren :: NodeG a c tag text -> c (NodeG a c tag text) Source #

getText :: Monoid text => NodeG a c tag text -> text Source #

modifyName :: (tag -> tag) -> NodeG a c tag text -> NodeG a c tag text Source #

modifyAttributes :: ([(tag, text)] -> [(tag, text)]) -> NodeG a c tag text -> NodeG a c tag text Source #

modifyChildren :: (c (NodeG a c tag text) -> c (NodeG a c tag text)) -> NodeG a c tag text -> NodeG a c tag text Source #

modifyElement :: ((tag, [(tag, text)], c (NodeG a c tag text)) -> (tag', [(tag', text)], c (NodeG a c tag' text))) -> NodeG a c tag text -> NodeG a c tag' text Source #

mapAllTags :: (tag -> tag') -> NodeG a c tag text -> NodeG a c tag' text Source #

mapNodeContainer :: List c' => (forall b. c b -> ItemM c (c' b)) -> NodeG a c tag text -> ItemM c (NodeG a c' tag text) Source #

mkText :: text -> NodeG a c tag text Source #

(Functor c, List c) => NodeClass (NodeG a) c Source # 

Methods

isElement :: NodeG a c tag text -> Bool Source #

isText :: NodeG a c tag text -> Bool Source #

isCData :: NodeG a c tag text -> Bool Source #

isProcessingInstruction :: NodeG a c tag text -> Bool Source #

isComment :: NodeG a c tag text -> Bool Source #

textContentM :: Monoid text => NodeG a c tag text -> ItemM c text Source #

isNamed :: Eq tag => tag -> NodeG a c tag text -> Bool Source #

getName :: Monoid tag => NodeG a c tag text -> tag Source #

hasTarget :: Eq text => text -> NodeG a c tag text -> Bool Source #

getTarget :: Monoid text => NodeG a c tag text -> text Source #

getAttributes :: NodeG a c tag text -> [(tag, text)] Source #

getChildren :: NodeG a c tag text -> c (NodeG a c tag text) Source #

getText :: Monoid text => NodeG a c tag text -> text Source #

modifyName :: (tag -> tag) -> NodeG a c tag text -> NodeG a c tag text Source #

modifyAttributes :: ([(tag, text)] -> [(tag, text)]) -> NodeG a c tag text -> NodeG a c tag text Source #

modifyChildren :: (c (NodeG a c tag text) -> c (NodeG a c tag text)) -> NodeG a c tag text -> NodeG a c tag text Source #

modifyElement :: ((tag, [(tag, text)], c (NodeG a c tag text)) -> (tag', [(tag', text)], c (NodeG a c tag' text))) -> NodeG a c tag text -> NodeG a c tag' text Source #

mapAllTags :: (tag -> tag') -> NodeG a c tag text -> NodeG a c tag' text Source #

mapNodeContainer :: List c' => (forall b. c b -> ItemM c (c' b)) -> NodeG a c tag text -> ItemM c (NodeG a c' tag text) Source #

mkText :: text -> NodeG a c tag text Source #

mapNodeListContainer :: (NodeClass n c, List c') => (forall a. c a -> ItemM c (c' a)) -> c (n c tag text) -> ItemM c (c' (n c' tag text)) Source #

Change a list of nodes recursively from one container type to another, with a specified function to convert the container type.

fromNodeContainer :: (NodeClass n c, List c') => n c tag text -> ItemM c (n c' tag text) Source #

Change a node recursively from one container type to another. This extracts the entire tree contents to standard lists and re-constructs them with the new container type. For monadic list types used in hexpat-iteratee this operation forces evaluation.

fromNodeListContainer :: (NodeClass n c, List c') => c (n c tag text) -> ItemM c (c' (n c' tag text)) Source #

Change a list of nodes recursively from one container type to another. This extracts the entire tree contents to standard lists and re-constructs them with the new container type. For monadic list types used in hexpat-iteratee this operation forces evaluation.

class NodeClass n c => MkElementClass n c where Source #

A class of node types where an Element can be constructed given a tag, attributes and children.

Minimal complete definition

mkElement

Methods

mkElement :: tag -> Attributes tag text -> c (n c tag text) -> n c tag text Source #

Generic element constructor.

Instances

(Functor c, List c) => MkElementClass NodeG c Source # 

Methods

mkElement :: tag -> Attributes tag text -> c (NodeG c tag text) -> NodeG c tag text Source #

(Functor c, List c) => MkElementClass (NodeG (Maybe a)) c Source # 

Methods

mkElement :: tag -> Attributes tag text -> c (NodeG (Maybe a) c tag text) -> NodeG (Maybe a) c tag text Source #

(Functor c, List c) => MkElementClass (NodeG ()) c Source # 

Methods

mkElement :: tag -> Attributes tag text -> c (NodeG () c tag text) -> NodeG () c tag text Source #

(Functor c, List c) => MkElementClass (NodeG (Maybe a)) c Source # 

Methods

mkElement :: tag -> Attributes tag text -> c (NodeG (Maybe a) c tag text) -> NodeG (Maybe a) c tag text Source #

(Functor c, List c) => MkElementClass (NodeG ()) c Source # 

Methods

mkElement :: tag -> Attributes tag text -> c (NodeG () c tag text) -> NodeG () c tag text Source #

getAttribute :: (NodeClass n c, GenericXMLString tag) => n c tag text -> tag -> Maybe text Source #

Get the value of the attribute having the specified name.

setAttribute :: (Eq tag, NodeClass n c, GenericXMLString tag) => tag -> text -> n c tag text -> n c tag text Source #

Set the value of the attribute with the specified name to the value, overwriting the first existing attribute with that name if present.

deleteAttribute :: (Eq tag, NodeClass n c, GenericXMLString tag) => tag -> n c tag text -> n c tag text Source #

Delete the first attribute matching the specified name.

alterAttribute :: (Eq tag, NodeClass n c, GenericXMLString tag) => tag -> Maybe text -> n c tag text -> n c tag text Source #

setAttribute if Just, deleteAttribute if Nothing.

fromElement :: (NodeClass n c, MkElementClass n' c, Monoid tag, Monoid text) => n c tag text -> n' c tag text Source #

Generically convert an element of one node type to another. Useful for adding or removing annotations.

fromElement_ Source #

Arguments

:: (NodeClass n c, NodeClass n' c, Monoid tag, Monoid text) 
=> (tag -> Attributes tag text -> c (n' c tag text) -> n' c tag text)

Element constructor

-> n c tag text 
-> n' c tag text 

Generically convert an element of one node type to another, using the specified element constructor. Useful for adding or removing annotations.

fromNodes :: (NodeClass n c, MkElementClass n' c, Monoid tag, Monoid text) => c (n c tag text) -> c (n' c tag text) Source #

Generically convert a list of nodes from one node type to another. Useful for adding or removing annotations.

fromNodes_ Source #

Arguments

:: (NodeClass n c, NodeClass n' c, Monoid tag, Monoid text) 
=> (tag -> Attributes tag text -> c (n' c tag text) -> n' c tag text)

Element constructor

-> c (n c tag text) 
-> c (n' c tag text) 

Generically convert a list of nodes from one node type to another, using the specified element constructor. Useful for adding or removing annotations.