{-# LANGUAGE OverloadedStrings #-}
module Data.XML.Parser.Mid.Attribute
( Attribute(..)
, attribute
) where
import Data.XML.Parser.Low
import Text.Parser.Char
import Text.Parser.Combinators
data Attribute = Attribute QName [Content]
deriving (Attribute -> Attribute -> Bool
(Attribute -> Attribute -> Bool)
-> (Attribute -> Attribute -> Bool) -> Eq Attribute
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Attribute -> Attribute -> Bool
$c/= :: Attribute -> Attribute -> Bool
== :: Attribute -> Attribute -> Bool
$c== :: Attribute -> Attribute -> Bool
Eq, Eq Attribute
Eq Attribute
-> (Attribute -> Attribute -> Ordering)
-> (Attribute -> Attribute -> Bool)
-> (Attribute -> Attribute -> Bool)
-> (Attribute -> Attribute -> Bool)
-> (Attribute -> Attribute -> Bool)
-> (Attribute -> Attribute -> Attribute)
-> (Attribute -> Attribute -> Attribute)
-> Ord Attribute
Attribute -> Attribute -> Bool
Attribute -> Attribute -> Ordering
Attribute -> Attribute -> Attribute
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Attribute -> Attribute -> Attribute
$cmin :: Attribute -> Attribute -> Attribute
max :: Attribute -> Attribute -> Attribute
$cmax :: Attribute -> Attribute -> Attribute
>= :: Attribute -> Attribute -> Bool
$c>= :: Attribute -> Attribute -> Bool
> :: Attribute -> Attribute -> Bool
$c> :: Attribute -> Attribute -> Bool
<= :: Attribute -> Attribute -> Bool
$c<= :: Attribute -> Attribute -> Bool
< :: Attribute -> Attribute -> Bool
$c< :: Attribute -> Attribute -> Bool
compare :: Attribute -> Attribute -> Ordering
$ccompare :: Attribute -> Attribute -> Ordering
$cp1Ord :: Eq Attribute
Ord, ReadPrec [Attribute]
ReadPrec Attribute
Int -> ReadS Attribute
ReadS [Attribute]
(Int -> ReadS Attribute)
-> ReadS [Attribute]
-> ReadPrec Attribute
-> ReadPrec [Attribute]
-> Read Attribute
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Attribute]
$creadListPrec :: ReadPrec [Attribute]
readPrec :: ReadPrec Attribute
$creadPrec :: ReadPrec Attribute
readList :: ReadS [Attribute]
$creadList :: ReadS [Attribute]
readsPrec :: Int -> ReadS Attribute
$creadsPrec :: Int -> ReadS Attribute
Read, Int -> Attribute -> ShowS
[Attribute] -> ShowS
Attribute -> String
(Int -> Attribute -> ShowS)
-> (Attribute -> String)
-> ([Attribute] -> ShowS)
-> Show Attribute
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Attribute] -> ShowS
$cshowList :: [Attribute] -> ShowS
show :: Attribute -> String
$cshow :: Attribute -> String
showsPrec :: Int -> Attribute -> ShowS
$cshowsPrec :: Int -> Attribute -> ShowS
Show)
attribute :: CharParsing m => Monad m => m Attribute
attribute :: m Attribute
attribute = do
QName
key <- m QName
forall (m :: * -> *). (CharParsing m, Monad m) => m QName
tokenQualifiedName
m ()
forall (m :: * -> *). (CharParsing m, Monad m) => m ()
tokenEqual
Char
quote <- String -> m Char
forall (m :: * -> *). CharParsing m => String -> m Char
oneOf String
"'\""
[Content]
value <- m Content -> m [Content]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
many (m Content -> m [Content]) -> m Content -> m [Content]
forall a b. (a -> b) -> a -> b
$ String -> m Content
forall (m :: * -> *).
(CharParsing m, Monad m) =>
String -> m Content
tokenContent [Char
quote, Char
'<']
Char -> m Char
forall (m :: * -> *). CharParsing m => Char -> m Char
char Char
quote
Attribute -> m Attribute
forall (m :: * -> *) a. Monad m => a -> m a
return (Attribute -> m Attribute) -> Attribute -> m Attribute
forall a b. (a -> b) -> a -> b
$ QName -> [Content] -> Attribute
Attribute QName
key [Content]
value