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

Safe HaskellSafe
LanguageHaskell98

Text.XML.Basic.Attribute

Contents

Synopsis

Documentation

data T name string Source #

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

Constructors

Cons 

Fields

Instances
Functor (T name) Source # 
Instance details

Defined in Text.XML.Basic.Attribute

Methods

fmap :: (a -> b) -> T name a -> T name b #

(<$) :: a -> T name b -> T name a #

Foldable (T name) Source # 
Instance details

Defined in Text.XML.Basic.Attribute

Methods

fold :: Monoid m => T name m -> m #

foldMap :: Monoid m => (a -> m) -> T name a -> m #

foldr :: (a -> b -> b) -> b -> T name a -> b #

foldr' :: (a -> b -> b) -> b -> T name a -> b #

foldl :: (b -> a -> b) -> b -> T name a -> b #

foldl' :: (b -> a -> b) -> b -> T name a -> b #

foldr1 :: (a -> a -> a) -> T name a -> a #

foldl1 :: (a -> a -> a) -> T name a -> a #

toList :: T name a -> [a] #

null :: T name a -> Bool #

length :: T name a -> Int #

elem :: Eq a => a -> T name a -> Bool #

maximum :: Ord a => T name a -> a #

minimum :: Ord a => T name a -> a #

sum :: Num a => T name a -> a #

product :: Num a => T name a -> a #

Traversable (T name) Source # 
Instance details

Defined in Text.XML.Basic.Attribute

Methods

traverse :: Applicative f => (a -> f b) -> T name a -> f (T name b) #

sequenceA :: Applicative f => T name (f a) -> f (T name a) #

mapM :: Monad m => (a -> m b) -> T name a -> m (T name b) #

sequence :: Monad m => T name (m a) -> m (T name a) #

(Eq name, Eq string) => Eq (T name string) Source # 
Instance details

Defined in Text.XML.Basic.Attribute

Methods

(==) :: T name string -> T name string -> Bool #

(/=) :: T name string -> T name string -> Bool #

(Ord name, Ord string) => Ord (T name string) Source # 
Instance details

Defined in Text.XML.Basic.Attribute

Methods

compare :: T name string -> T name string -> Ordering #

(<) :: T name string -> T name string -> Bool #

(<=) :: T name string -> T name string -> Bool #

(>) :: T name string -> T name string -> Bool #

(>=) :: T name string -> T name string -> Bool #

max :: T name string -> T name string -> T name string #

min :: T name string -> T name string -> T name string #

(Attribute name, Show string) => Show (T name string) Source # 
Instance details

Defined in Text.XML.Basic.Attribute

Methods

showsPrec :: Int -> T name string -> ShowS #

show :: T name string -> String #

showList :: [T name string] -> ShowS #

(Attribute name, C string) => C (T name string) Source # 
Instance details

Defined in Text.XML.Basic.Attribute

Methods

run :: T name string -> ShowS Source #

cons :: Attribute name => Name name -> string -> T name string Source #

new :: Attribute name => String -> string -> T name string Source #

lift :: (Name name -> string -> (Name name, string)) -> T name string -> T name string Source #

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

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

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

value :: T (T name string) string Source #

formatListBlankHead :: (Attribute name, C string) => [T name string] -> ShowS Source #

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 string Source #

newtype Name ident Source #

Constructors

Name 

Fields

Instances
Eq ident => Eq (Name ident) Source # 
Instance details

Defined in Text.XML.Basic.Attribute

Methods

(==) :: Name ident -> Name ident -> Bool #

(/=) :: Name ident -> Name ident -> Bool #

Ord ident => Ord (Name ident) Source # 
Instance details

Defined in Text.XML.Basic.Attribute

Methods

compare :: Name ident -> Name ident -> Ordering #

(<) :: Name ident -> Name ident -> Bool #

(<=) :: Name ident -> Name ident -> Bool #

(>) :: Name ident -> Name ident -> Bool #

(>=) :: Name ident -> Name ident -> Bool #

max :: Name ident -> Name ident -> Name ident #

min :: Name ident -> Name ident -> Name ident #

Show ident => Show (Name ident) Source # 
Instance details

Defined in Text.XML.Basic.Attribute

Methods

showsPrec :: Int -> Name ident -> ShowS #

show :: Name ident -> String #

showList :: [Name ident] -> ShowS #

Attribute ident => C (Name ident) Source # 
Instance details

Defined in Text.XML.Basic.Attribute

Methods

fromString :: String -> Name ident Source #

toString :: Name ident -> String Source #

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 -> Bool Source #

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

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 string Source #

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

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

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

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

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

anyNameLit :: Attribute name => String -> [T name string] -> Bool Source #

anyValueLit :: Eq string => string -> [T name string] -> Bool Source #