xml-basic-0.1.1: Basics for XML/HTML representation and processing

Text.XML.Basic.Attribute

Contents

Synopsis

Documentation

data T name string Source

An HTML attribute id="name" generates ("id","name")

Constructors

Cons 

Fields

name_ :: Name name
 
value_ :: string
 

Instances

Functor (T name) 
Foldable (T name) 
Traversable (T name) 
(Eq name, Eq string) => Eq (T name string) 
(Ord name, Ord string) => Ord (T name string) 
(Attribute name, Show string) => Show (T name string) 
(Attribute name, C string) => C (T name string) 

cons :: Attribute name => Name name -> string -> T name stringSource

new :: Attribute name => String -> string -> T name stringSource

lift :: (Name name -> string -> (Name name, string)) -> T name string -> T name stringSource

toPair :: Attribute name => T name string -> (String, string)Source

fromPair :: Attribute name => (String, string) -> T name stringSource

name :: T (T name string) (Name name)Source

value :: T (T name string) stringSource

formatListBlankHead :: (Attribute name, C string) => [T name string] -> ShowSSource

Each attribute is preceded by a space, that is there is a space between adjacent attributes and one leading space.

mapName :: (Name name0 -> Name name1) -> T name0 string -> T name1 stringSource

newtype Name ident Source

Constructors

Name 

Fields

unname :: ident
 

Instances

Eq ident => Eq (Name ident) 
Ord ident => Ord (Name ident) 
Show ident => Show (Name ident) 
Attribute ident => C (Name ident) 

attribute lists

mapValues :: (str0 -> str1) -> [T name str0] -> [T name str1]Source

mapValuesA :: Applicative f => (str0 -> f str1) -> [T name str0] -> f [T name str1]Source

adjustOn :: (Name name -> Bool) -> (string -> string) -> [T name string] -> [T name string]Source

Process specific attributes of an attribute list. The function name is inspired by Data.Map.

adjustOnA :: Applicative f => (Name name -> Bool) -> (string -> f string) -> [T name string] -> f [T name string]Source

insert :: Attribute name => Name name -> string -> [T name string] -> [T name string]Source

insertWith :: Attribute name => (string -> string -> string) -> Name name -> string -> [T name string] -> [T name string]Source

Insert an attribute into an attribute list. If an attribute with the same name is already present, then the value of this attribute is changed to f newValue oldValue. The function name is analogous to Data.Map.

match attributes

match :: (Attribute name, Eq string) => String -> string -> T name string -> BoolSource

matchAnyValue :: (Attribute name, Eq string) => String -> [string] -> T name string -> BoolSource

matchManyValues name [value0, value1] attrs checks whether (name, value0) or (name, value1) is contained in attrs. The values are handled case-sensitive.

lookup :: Attribute name => Name name -> [T name string] -> Maybe stringSource

lookupLit :: Attribute name => String -> [T name string] -> Maybe stringSource

any :: (T name string -> Bool) -> [T name string] -> BoolSource

anyName :: (Name name -> Bool) -> [T name string] -> BoolSource

anyValue :: (string -> Bool) -> [T name string] -> BoolSource

anyLit :: (Attribute name, Eq string) => String -> string -> [T name string] -> BoolSource

anyNameLit :: Attribute name => String -> [T name string] -> BoolSource

anyValueLit :: Eq string => string -> [T name string] -> BoolSource