{-# LANGUAGE CPP #-}
module Text.XML.HaXml.Html.Pretty
( document
, element
, attribute
, content
) where
#if MIN_VERSION_base(4,11,0)
import Prelude hiding (maybe,either,(<>))
#else
import Prelude hiding (maybe,either)
#endif
import Data.Maybe hiding (maybe)
import Data.List (intersperse)
import Data.Char (isSpace)
import Text.PrettyPrint.HughesPJ
import Text.XML.HaXml.Types
import Text.XML.HaXml.Namespaces
either :: (a->c) -> (b->c) -> Either a b -> c
either :: forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either a -> c
f b -> c
_g (Left a
x) = a -> c
f a
x
either a -> c
_f b -> c
g (Right b
x) = b -> c
g b
x
maybe :: (a->Doc) -> Maybe a -> Doc
maybe :: forall a. (a -> Doc) -> Maybe a -> Doc
maybe a -> Doc
_f Maybe a
Nothing = Doc
empty
maybe a -> Doc
f (Just a
x) = a -> Doc
f a
x
document :: Document i -> Doc
prolog :: Prolog -> Doc
xmldecl :: XMLDecl -> Doc
misc :: Misc -> Doc
sddecl :: Bool -> Doc
doctypedecl :: DocTypeDecl -> Doc
markupdecl :: MarkupDecl -> Doc
element :: Element i -> Doc
attribute :: Attribute -> Doc
content :: Content i -> Doc
document :: forall i. Document i -> Doc
document (Document Prolog
p SymTab EntityDef
_ Element i
e [Misc]
m)= Prolog -> Doc
prolog Prolog
p Doc -> Doc -> Doc
$$ forall i. Element i -> Doc
element Element i
e Doc -> Doc -> Doc
$$ [Doc] -> Doc
vcat (forall a b. (a -> b) -> [a] -> [b]
map Misc -> Doc
misc [Misc]
m)
prolog :: Prolog -> Doc
prolog (Prolog Maybe XMLDecl
x [Misc]
m1 Maybe DocTypeDecl
dtd [Misc]
m2)= forall a. (a -> Doc) -> Maybe a -> Doc
maybe XMLDecl -> Doc
xmldecl Maybe XMLDecl
x Doc -> Doc -> Doc
$$
[Doc] -> Doc
vcat (forall a b. (a -> b) -> [a] -> [b]
map Misc -> Doc
misc [Misc]
m1) Doc -> Doc -> Doc
$$
forall a. (a -> Doc) -> Maybe a -> Doc
maybe DocTypeDecl -> Doc
doctypedecl Maybe DocTypeDecl
dtd Doc -> Doc -> Doc
$$
[Doc] -> Doc
vcat (forall a b. (a -> b) -> [a] -> [b]
map Misc -> Doc
misc [Misc]
m2)
xmldecl :: XMLDecl -> Doc
xmldecl (XMLDecl VersionInfo
v Maybe EncodingDecl
e Maybe SDDecl
sd) = VersionInfo -> Doc
text VersionInfo
"<?xml version='" Doc -> Doc -> Doc
<> VersionInfo -> Doc
text VersionInfo
v Doc -> Doc -> Doc
<> VersionInfo -> Doc
text VersionInfo
"'" Doc -> Doc -> Doc
<+>
forall a. (a -> Doc) -> Maybe a -> Doc
maybe EncodingDecl -> Doc
encodingdecl Maybe EncodingDecl
e Doc -> Doc -> Doc
<+>
forall a. (a -> Doc) -> Maybe a -> Doc
maybe SDDecl -> Doc
sddecl Maybe SDDecl
sd Doc -> Doc -> Doc
<+>
VersionInfo -> Doc
text VersionInfo
"?>"
misc :: Misc -> Doc
misc (Comment VersionInfo
s) = VersionInfo -> Doc
text VersionInfo
"<!--" Doc -> Doc -> Doc
<+> VersionInfo -> Doc
text VersionInfo
s Doc -> Doc -> Doc
<+> VersionInfo -> Doc
text VersionInfo
"-->"
misc (PI (VersionInfo
n,VersionInfo
s)) = VersionInfo -> Doc
text VersionInfo
"<?" Doc -> Doc -> Doc
<> VersionInfo -> Doc
text VersionInfo
n Doc -> Doc -> Doc
<+> VersionInfo -> Doc
text VersionInfo
s Doc -> Doc -> Doc
<+> VersionInfo -> Doc
text VersionInfo
"?>"
sddecl :: SDDecl -> Doc
sddecl SDDecl
sd | SDDecl
sd = VersionInfo -> Doc
text VersionInfo
"standalone='yes'"
| SDDecl
otherwise = VersionInfo -> Doc
text VersionInfo
"standalone='no'"
doctypedecl :: DocTypeDecl -> Doc
doctypedecl (DTD QName
n Maybe ExternalID
eid [MarkupDecl]
ds) = if forall (t :: * -> *) a. Foldable t => t a -> SDDecl
null [MarkupDecl]
ds then
Doc
hd Doc -> Doc -> Doc
<> VersionInfo -> Doc
text VersionInfo
">"
else Doc
hd Doc -> Doc -> Doc
<+> VersionInfo -> Doc
text VersionInfo
" [" Doc -> Doc -> Doc
$$
[Doc] -> Doc
vcat (forall a b. (a -> b) -> [a] -> [b]
map MarkupDecl -> Doc
markupdecl [MarkupDecl]
ds) Doc -> Doc -> Doc
$$ VersionInfo -> Doc
text VersionInfo
"]>"
where hd :: Doc
hd = VersionInfo -> Doc
text VersionInfo
"<!DOCTYPE" Doc -> Doc -> Doc
<+> QName -> Doc
qname QName
n Doc -> Doc -> Doc
<+>
forall a. (a -> Doc) -> Maybe a -> Doc
maybe ExternalID -> Doc
externalid Maybe ExternalID
eid
markupdecl :: MarkupDecl -> Doc
markupdecl (Element ElementDecl
e) = ElementDecl -> Doc
elementdecl ElementDecl
e
markupdecl (AttList AttListDecl
a) = AttListDecl -> Doc
attlistdecl AttListDecl
a
markupdecl (Entity EntityDecl
e) = EntityDecl -> Doc
entitydecl EntityDecl
e
markupdecl (Notation NotationDecl
n) = NotationDecl -> Doc
notationdecl NotationDecl
n
markupdecl (MarkupMisc Misc
m) = Misc -> Doc
misc Misc
m
element :: forall i. Element i -> Doc
element (Elem QName
n [Attribute]
as []) = VersionInfo -> Doc
text VersionInfo
"<" Doc -> Doc -> Doc
<> QName -> Doc
qname QName
n Doc -> Doc -> Doc
<+>
[Doc] -> Doc
fsep (forall a b. (a -> b) -> [a] -> [b]
map Attribute -> Doc
attribute [Attribute]
as) Doc -> Doc -> Doc
<> VersionInfo -> Doc
text VersionInfo
"/>"
element e :: Element i
e@(Elem QName
n [Attribute]
as [Content i]
cs)
| forall i. Content i -> SDDecl
isText (forall a. [a] -> a
head [Content i]
cs) = VersionInfo -> Doc
text VersionInfo
"<" Doc -> Doc -> Doc
<> QName -> Doc
qname QName
n Doc -> Doc -> Doc
<+> [Doc] -> Doc
fsep (forall a b. (a -> b) -> [a] -> [b]
map Attribute -> Doc
attribute [Attribute]
as) Doc -> Doc -> Doc
<>
VersionInfo -> Doc
text VersionInfo
">" Doc -> Doc -> Doc
<> [Doc] -> Doc
hcat (forall a b. (a -> b) -> [a] -> [b]
map forall i. Content i -> Doc
content [Content i]
cs) Doc -> Doc -> Doc
<>
VersionInfo -> Doc
text VersionInfo
"</" Doc -> Doc -> Doc
<> QName -> Doc
qname QName
n Doc -> Doc -> Doc
<> VersionInfo -> Doc
text VersionInfo
">"
| SDDecl
otherwise = let (Doc
d,Doc
c) = forall i. Element i -> Doc -> (Doc, Doc)
carryelem Element i
e Doc
empty
in Doc
d Doc -> Doc -> Doc
<> Doc
c
isText :: Content i -> Bool
isText :: forall i. Content i -> SDDecl
isText (CString SDDecl
_ VersionInfo
_ i
_) = SDDecl
True
isText (CRef Reference
_ i
_) = SDDecl
True
isText Content i
_ = SDDecl
False
carryelem :: Element i -> Doc -> (Doc, Doc)
carryelem :: forall i. Element i -> Doc -> (Doc, Doc)
carryelem (Elem QName
n [Attribute]
as []) Doc
c
= ( Doc
c Doc -> Doc -> Doc
<>
VersionInfo -> Doc
text VersionInfo
"<" Doc -> Doc -> Doc
<> QName -> Doc
qname QName
n Doc -> Doc -> Doc
<+> [Doc] -> Doc
fsep (forall a b. (a -> b) -> [a] -> [b]
map Attribute -> Doc
attribute [Attribute]
as)
, VersionInfo -> Doc
text VersionInfo
"/>")
carryelem (Elem QName
n [Attribute]
as [Content i]
cs) Doc
c
| forall i. Content i -> SDDecl
isText (forall a. [a] -> a
head [Content i]
cs) =
( Doc
start Doc -> Doc -> Doc
<>
VersionInfo -> Doc
text VersionInfo
">" Doc -> Doc -> Doc
<> [Doc] -> Doc
hcat (forall a b. (a -> b) -> [a] -> [b]
map forall i. Content i -> Doc
content [Content i]
cs) Doc -> Doc -> Doc
<> VersionInfo -> Doc
text VersionInfo
"</" Doc -> Doc -> Doc
<> QName -> Doc
qname QName
n
, VersionInfo -> Doc
text VersionInfo
">")
| SDDecl
otherwise =
let (Doc
d,Doc
c') = forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl forall i. (Doc, Doc) -> Content i -> (Doc, Doc)
carrycontent (Doc
start, VersionInfo -> Doc
text VersionInfo
">") [Content i]
cs in
( Doc
d Doc -> Doc -> Doc
<> Doc
c' Doc -> Doc -> Doc
<> VersionInfo -> Doc
text VersionInfo
"</" Doc -> Doc -> Doc
<> QName -> Doc
qname QName
n
, VersionInfo -> Doc
text VersionInfo
">")
where start :: Doc
start = Doc
c Doc -> Doc -> Doc
<> VersionInfo -> Doc
text VersionInfo
"<" Doc -> Doc -> Doc
<> QName -> Doc
qname QName
n Doc -> Doc -> Doc
<+> [Doc] -> Doc
fsep (forall a b. (a -> b) -> [a] -> [b]
map Attribute -> Doc
attribute [Attribute]
as)
carrycontent :: (Doc, Doc) -> Content i -> (Doc, Doc)
carrycontent :: forall i. (Doc, Doc) -> Content i -> (Doc, Doc)
carrycontent (Doc
d,Doc
c) (CElem Element i
e i
_) = let (Doc
d',Doc
c') = forall i. Element i -> Doc -> (Doc, Doc)
carryelem Element i
e Doc
c in
(Doc
d Doc -> Doc -> Doc
$$ CharRef -> Doc -> Doc
nest CharRef
2 Doc
d', Doc
c')
carrycontent (Doc
d,Doc
c) (CString SDDecl
_ VersionInfo
s i
_) = (Doc
d Doc -> Doc -> Doc
<> Doc
c Doc -> Doc -> Doc
<> VersionInfo -> Doc
chardata VersionInfo
s, Doc
empty)
carrycontent (Doc
d,Doc
c) (CRef Reference
r i
_) = (Doc
d Doc -> Doc -> Doc
<> Doc
c Doc -> Doc -> Doc
<> Reference -> Doc
reference Reference
r,Doc
empty)
carrycontent (Doc
d,Doc
c) (CMisc Misc
m i
_) = (Doc
d Doc -> Doc -> Doc
$$ Doc
c Doc -> Doc -> Doc
<> Misc -> Doc
misc Misc
m, Doc
empty)
attribute :: Attribute -> Doc
attribute (QName
n,AttValue
v) = QName -> Doc
qname QName
n Doc -> Doc -> Doc
<> VersionInfo -> Doc
text VersionInfo
"=" Doc -> Doc -> Doc
<> AttValue -> Doc
attvalue AttValue
v
content :: forall i. Content i -> Doc
content (CElem Element i
e i
_) = forall i. Element i -> Doc
element Element i
e
content (CString SDDecl
_ VersionInfo
s i
_) = VersionInfo -> Doc
chardata VersionInfo
s
content (CRef Reference
r i
_) = Reference -> Doc
reference Reference
r
content (CMisc Misc
m i
_) = Misc -> Doc
misc Misc
m
elementdecl :: ElementDecl -> Doc
contentspec :: ContentSpec -> Doc
cp :: CP -> Doc
modifier :: Modifier -> Doc
mixed :: Mixed -> Doc
attlistdecl :: AttListDecl -> Doc
attdef :: AttDef -> Doc
atttype :: AttType -> Doc
tokenizedtype :: TokenizedType -> Doc
enumeratedtype :: EnumeratedType -> Doc
notationtype :: [String] -> Doc
enumeration :: [String] -> Doc
defaultdecl :: DefaultDecl -> Doc
reference :: Reference -> Doc
entityref :: String -> Doc
charref :: (Show a) => a -> Doc
entitydecl :: EntityDecl -> Doc
gedecl :: GEDecl -> Doc
pedecl :: PEDecl -> Doc
entitydef :: EntityDef -> Doc
pedef :: PEDef -> Doc
externalid :: ExternalID -> Doc
ndatadecl :: NDataDecl -> Doc
notationdecl :: NotationDecl -> Doc
publicid :: PublicID -> Doc
encodingdecl :: EncodingDecl -> Doc
nmtoken :: String -> Doc
attvalue :: AttValue -> Doc
entityvalue :: EntityValue -> Doc
ev :: EV -> Doc
pubidliteral :: PubidLiteral -> Doc
systemliteral :: SystemLiteral -> Doc
chardata :: [Char] -> Doc
elementdecl :: ElementDecl -> Doc
elementdecl (ElementDecl QName
n ContentSpec
cs) = VersionInfo -> Doc
text VersionInfo
"<!ELEMENT" Doc -> Doc -> Doc
<+> QName -> Doc
qname QName
n Doc -> Doc -> Doc
<+>
ContentSpec -> Doc
contentspec ContentSpec
cs Doc -> Doc -> Doc
<> VersionInfo -> Doc
text VersionInfo
">"
contentspec :: ContentSpec -> Doc
contentspec ContentSpec
EMPTY = VersionInfo -> Doc
text VersionInfo
"EMPTY"
contentspec ContentSpec
ANY = VersionInfo -> Doc
text VersionInfo
"ANY"
contentspec (Mixed Mixed
m) = Mixed -> Doc
mixed Mixed
m
contentspec (ContentSpec CP
c) = CP -> Doc
cp CP
c
cp :: CP -> Doc
cp (TagName QName
n Modifier
m) = QName -> Doc
qname QName
n Doc -> Doc -> Doc
<> Modifier -> Doc
modifier Modifier
m
cp (Choice [CP]
cs Modifier
m) = Doc -> Doc
parens ([Doc] -> Doc
hcat (forall a. a -> [a] -> [a]
intersperse (VersionInfo -> Doc
text VersionInfo
"|") (forall a b. (a -> b) -> [a] -> [b]
map CP -> Doc
cp [CP]
cs))) Doc -> Doc -> Doc
<>
Modifier -> Doc
modifier Modifier
m
cp (Seq [CP]
cs Modifier
m) = Doc -> Doc
parens ([Doc] -> Doc
hcat (forall a. a -> [a] -> [a]
intersperse (VersionInfo -> Doc
text VersionInfo
",") (forall a b. (a -> b) -> [a] -> [b]
map CP -> Doc
cp [CP]
cs))) Doc -> Doc -> Doc
<>
Modifier -> Doc
modifier Modifier
m
modifier :: Modifier -> Doc
modifier Modifier
None = Doc
empty
modifier Modifier
Query = VersionInfo -> Doc
text VersionInfo
"?"
modifier Modifier
Star = VersionInfo -> Doc
text VersionInfo
"*"
modifier Modifier
Plus = VersionInfo -> Doc
text VersionInfo
"+"
mixed :: Mixed -> Doc
mixed Mixed
PCDATA = VersionInfo -> Doc
text VersionInfo
"(#PCDATA)"
mixed (PCDATAplus [QName]
ns) = VersionInfo -> Doc
text VersionInfo
"(#PCDATA |" Doc -> Doc -> Doc
<+>
[Doc] -> Doc
hcat (forall a. a -> [a] -> [a]
intersperse (VersionInfo -> Doc
text VersionInfo
"|") (forall a b. (a -> b) -> [a] -> [b]
map QName -> Doc
qname [QName]
ns)) Doc -> Doc -> Doc
<>
VersionInfo -> Doc
text VersionInfo
")*"
attlistdecl :: AttListDecl -> Doc
attlistdecl (AttListDecl QName
n [AttDef]
ds) = VersionInfo -> Doc
text VersionInfo
"<!ATTLIST" Doc -> Doc -> Doc
<+> QName -> Doc
qname QName
n Doc -> Doc -> Doc
<+>
[Doc] -> Doc
fsep (forall a b. (a -> b) -> [a] -> [b]
map AttDef -> Doc
attdef [AttDef]
ds) Doc -> Doc -> Doc
<> VersionInfo -> Doc
text VersionInfo
">"
attdef :: AttDef -> Doc
attdef (AttDef QName
n AttType
t DefaultDecl
d) = QName -> Doc
qname QName
n Doc -> Doc -> Doc
<+> AttType -> Doc
atttype AttType
t Doc -> Doc -> Doc
<+> DefaultDecl -> Doc
defaultdecl DefaultDecl
d
atttype :: AttType -> Doc
atttype AttType
StringType = VersionInfo -> Doc
text VersionInfo
"CDATA"
atttype (TokenizedType TokenizedType
t) = TokenizedType -> Doc
tokenizedtype TokenizedType
t
atttype (EnumeratedType EnumeratedType
t) = EnumeratedType -> Doc
enumeratedtype EnumeratedType
t
tokenizedtype :: TokenizedType -> Doc
tokenizedtype TokenizedType
ID = VersionInfo -> Doc
text VersionInfo
"ID"
tokenizedtype TokenizedType
IDREF = VersionInfo -> Doc
text VersionInfo
"IDREF"
tokenizedtype TokenizedType
IDREFS = VersionInfo -> Doc
text VersionInfo
"IDREFS"
tokenizedtype TokenizedType
ENTITY = VersionInfo -> Doc
text VersionInfo
"ENTITY"
tokenizedtype TokenizedType
ENTITIES = VersionInfo -> Doc
text VersionInfo
"ENTITIES"
tokenizedtype TokenizedType
NMTOKEN = VersionInfo -> Doc
text VersionInfo
"NMTOKEN"
tokenizedtype TokenizedType
NMTOKENS = VersionInfo -> Doc
text VersionInfo
"NMTOKENS"
enumeratedtype :: EnumeratedType -> Doc
enumeratedtype (NotationType NotationType
n)= NotationType -> Doc
notationtype NotationType
n
enumeratedtype (Enumeration NotationType
e) = NotationType -> Doc
enumeration NotationType
e
notationtype :: NotationType -> Doc
notationtype NotationType
ns = VersionInfo -> Doc
text VersionInfo
"NOTATION" Doc -> Doc -> Doc
<+>
Doc -> Doc
parens ([Doc] -> Doc
hcat (forall a. a -> [a] -> [a]
intersperse (VersionInfo -> Doc
text VersionInfo
"|") (forall a b. (a -> b) -> [a] -> [b]
map VersionInfo -> Doc
text NotationType
ns)))
enumeration :: NotationType -> Doc
enumeration NotationType
ns = Doc -> Doc
parens ([Doc] -> Doc
hcat (forall a. a -> [a] -> [a]
intersperse (VersionInfo -> Doc
text VersionInfo
"|") (forall a b. (a -> b) -> [a] -> [b]
map VersionInfo -> Doc
nmtoken NotationType
ns)))
defaultdecl :: DefaultDecl -> Doc
defaultdecl DefaultDecl
REQUIRED = VersionInfo -> Doc
text VersionInfo
"#REQUIRED"
defaultdecl DefaultDecl
IMPLIED = VersionInfo -> Doc
text VersionInfo
"#IMPLIED"
defaultdecl (DefaultTo AttValue
a Maybe FIXED
f) = forall a. (a -> Doc) -> Maybe a -> Doc
maybe (forall a b. a -> b -> a
const (VersionInfo -> Doc
text VersionInfo
"#FIXED")) Maybe FIXED
f Doc -> Doc -> Doc
<+> AttValue -> Doc
attvalue AttValue
a
reference :: Reference -> Doc
reference (RefEntity VersionInfo
er) = VersionInfo -> Doc
entityref VersionInfo
er
reference (RefChar CharRef
cr) = forall a. Show a => a -> Doc
charref CharRef
cr
entityref :: VersionInfo -> Doc
entityref VersionInfo
n = VersionInfo -> Doc
text VersionInfo
"&" Doc -> Doc -> Doc
<> VersionInfo -> Doc
text VersionInfo
n Doc -> Doc -> Doc
<> VersionInfo -> Doc
text VersionInfo
";"
charref :: forall a. Show a => a -> Doc
charref a
c = VersionInfo -> Doc
text VersionInfo
"&#" Doc -> Doc -> Doc
<> VersionInfo -> Doc
text (forall a. Show a => a -> VersionInfo
show a
c) Doc -> Doc -> Doc
<> VersionInfo -> Doc
text VersionInfo
";"
entitydecl :: EntityDecl -> Doc
entitydecl (EntityGEDecl GEDecl
d) = GEDecl -> Doc
gedecl GEDecl
d
entitydecl (EntityPEDecl PEDecl
d) = PEDecl -> Doc
pedecl PEDecl
d
gedecl :: GEDecl -> Doc
gedecl (GEDecl VersionInfo
n EntityDef
ed) = VersionInfo -> Doc
text VersionInfo
"<!ENTITY" Doc -> Doc -> Doc
<+> VersionInfo -> Doc
text VersionInfo
n Doc -> Doc -> Doc
<+> EntityDef -> Doc
entitydef EntityDef
ed Doc -> Doc -> Doc
<>
VersionInfo -> Doc
text VersionInfo
">"
pedecl :: PEDecl -> Doc
pedecl (PEDecl VersionInfo
n PEDef
pd) = VersionInfo -> Doc
text VersionInfo
"<!ENTITY %" Doc -> Doc -> Doc
<> VersionInfo -> Doc
text VersionInfo
n Doc -> Doc -> Doc
<+> PEDef -> Doc
pedef PEDef
pd Doc -> Doc -> Doc
<>
VersionInfo -> Doc
text VersionInfo
">"
entitydef :: EntityDef -> Doc
entitydef (DefEntityValue EntityValue
ev) = EntityValue -> Doc
entityvalue EntityValue
ev
entitydef (DefExternalID ExternalID
i Maybe NDataDecl
nd) = ExternalID -> Doc
externalid ExternalID
i Doc -> Doc -> Doc
<+> forall a. (a -> Doc) -> Maybe a -> Doc
maybe NDataDecl -> Doc
ndatadecl Maybe NDataDecl
nd
pedef :: PEDef -> Doc
pedef (PEDefEntityValue EntityValue
ev) = EntityValue -> Doc
entityvalue EntityValue
ev
pedef (PEDefExternalID ExternalID
eid) = ExternalID -> Doc
externalid ExternalID
eid
externalid :: ExternalID -> Doc
externalid (SYSTEM SystemLiteral
sl) = VersionInfo -> Doc
text VersionInfo
"SYSTEM" Doc -> Doc -> Doc
<+> SystemLiteral -> Doc
systemliteral SystemLiteral
sl
externalid (PUBLIC PubidLiteral
i SystemLiteral
sl) = VersionInfo -> Doc
text VersionInfo
"PUBLIC" Doc -> Doc -> Doc
<+> PubidLiteral -> Doc
pubidliteral PubidLiteral
i Doc -> Doc -> Doc
<+>
SystemLiteral -> Doc
systemliteral SystemLiteral
sl
ndatadecl :: NDataDecl -> Doc
ndatadecl (NDATA VersionInfo
n) = VersionInfo -> Doc
text VersionInfo
"NDATA" Doc -> Doc -> Doc
<+> VersionInfo -> Doc
text VersionInfo
n
notationdecl :: NotationDecl -> Doc
notationdecl (NOTATION VersionInfo
n Either ExternalID PublicID
e) = VersionInfo -> Doc
text VersionInfo
"<!NOTATION" Doc -> Doc -> Doc
<+> VersionInfo -> Doc
text VersionInfo
n Doc -> Doc -> Doc
<+>
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either ExternalID -> Doc
externalid PublicID -> Doc
publicid Either ExternalID PublicID
e Doc -> Doc -> Doc
<>
VersionInfo -> Doc
text VersionInfo
">"
publicid :: PublicID -> Doc
publicid (PUBLICID PubidLiteral
p) = VersionInfo -> Doc
text VersionInfo
"PUBLICID" Doc -> Doc -> Doc
<+> PubidLiteral -> Doc
pubidliteral PubidLiteral
p
encodingdecl :: EncodingDecl -> Doc
encodingdecl (EncodingDecl VersionInfo
s) = VersionInfo -> Doc
text VersionInfo
"encoding='" Doc -> Doc -> Doc
<> VersionInfo -> Doc
text VersionInfo
s Doc -> Doc -> Doc
<> VersionInfo -> Doc
text VersionInfo
"'"
nmtoken :: VersionInfo -> Doc
nmtoken VersionInfo
s = VersionInfo -> Doc
text VersionInfo
s
attvalue :: AttValue -> Doc
attvalue (AttValue [Either VersionInfo Reference]
esr) = VersionInfo -> Doc
text VersionInfo
"\"" Doc -> Doc -> Doc
<>
[Doc] -> Doc
hcat (forall a b. (a -> b) -> [a] -> [b]
map (forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either VersionInfo -> Doc
text Reference -> Doc
reference) [Either VersionInfo Reference]
esr) Doc -> Doc -> Doc
<>
VersionInfo -> Doc
text VersionInfo
"\""
entityvalue :: EntityValue -> Doc
entityvalue (EntityValue [EV]
evs) = VersionInfo -> Doc
text VersionInfo
"'" Doc -> Doc -> Doc
<> [Doc] -> Doc
hcat (forall a b. (a -> b) -> [a] -> [b]
map EV -> Doc
ev [EV]
evs) Doc -> Doc -> Doc
<> VersionInfo -> Doc
text VersionInfo
"'"
ev :: EV -> Doc
ev (EVString VersionInfo
s) = VersionInfo -> Doc
text VersionInfo
s
ev (EVRef Reference
r) = Reference -> Doc
reference Reference
r
pubidliteral :: PubidLiteral -> Doc
pubidliteral (PubidLiteral VersionInfo
s) = VersionInfo -> Doc
text VersionInfo
"'" Doc -> Doc -> Doc
<> VersionInfo -> Doc
text VersionInfo
s Doc -> Doc -> Doc
<> VersionInfo -> Doc
text VersionInfo
"'"
systemliteral :: SystemLiteral -> Doc
systemliteral (SystemLiteral VersionInfo
s)= VersionInfo -> Doc
text VersionInfo
"'" Doc -> Doc -> Doc
<> VersionInfo -> Doc
text VersionInfo
s Doc -> Doc -> Doc
<> VersionInfo -> Doc
text VersionInfo
"'"
chardata :: VersionInfo -> Doc
chardata VersionInfo
s = if forall (t :: * -> *) a.
Foldable t =>
(a -> SDDecl) -> t a -> SDDecl
all Char -> SDDecl
isSpace VersionInfo
s then Doc
empty else VersionInfo -> Doc
text VersionInfo
s
qname :: QName -> Doc
qname QName
n = VersionInfo -> Doc
text (QName -> VersionInfo
printableName QName
n)