Safe Haskell | None |
---|---|
Language | Haskell98 |
A non-validating XML parser. For the input grammar, see http://www.w3.org/TR/REC-xml.
Synopsis
- xmlParse :: String -> String -> Document Posn
- xmlParse' :: String -> String -> Either String (Document Posn)
- dtdParse :: String -> String -> Maybe DocTypeDecl
- dtdParse' :: String -> String -> Either String (Maybe DocTypeDecl)
- xmlParseWith :: XParser a -> [(Posn, TokenT)] -> (Either String a, [(Posn, TokenT)])
- document :: XParser (Document Posn)
- element :: XParser (Element Posn)
- content :: XParser (Content Posn)
- comment :: XParser Comment
- cdsect :: XParser CDSect
- chardata :: XParser CharData
- reference :: XParser Reference
- doctypedecl :: XParser DocTypeDecl
- processinginstruction :: XParser ProcessingInstruction
- elemtag :: XParser ElemTag
- qname :: XParser QName
- name :: XParser Name
- tok :: TokenT -> XParser TokenT
- elemOpenTag :: XParser ElemTag
- elemCloseTag :: QName -> XParser ()
- emptySTs :: SymTabs
- type XParser a = Parser SymTabs (Posn, TokenT) a
- fst3 :: (a, b, c) -> a
- snd3 :: (a, b, c) -> b
- thd3 :: (a, b, c) -> c
Parse a whole document
xmlParse :: String -> String -> Document Posn Source #
To parse a whole document, xmlParse file content
takes a filename
(for generating error reports) and the string content of that file.
A parse error causes program failure, with message to stderr.
xmlParse' :: String -> String -> Either String (Document Posn) Source #
To parse a whole document, xmlParse' file content
takes a filename
(for generating error reports) and the string content of that file.
Any parse error message is passed back to the caller through the
Either
type.
Parse just a DTD
dtdParse :: String -> String -> Maybe DocTypeDecl Source #
To parse just a DTD, dtdParse file content
takes a filename
(for generating error reports) and the string content of that
file. If no DTD was found, you get Nothing
rather than an error.
However, if a DTD is found but contains errors, the program crashes.
dtdParse' :: String -> String -> Either String (Maybe DocTypeDecl) Source #
To parse just a DTD, dtdParse' file content
takes a filename
(for generating error reports) and the string content of that
file. If no DTD was found, you get Right Nothing
.
If a DTD was found but contains errors, you get a Left message
.
Parse a partial document
xmlParseWith :: XParser a -> [(Posn, TokenT)] -> (Either String a, [(Posn, TokenT)]) Source #
To parse a partial document, e.g. from an XML-based stream protocol, where you may later want to get more document elements from the same stream. Arguments are: a parser for the item you want, and the already-lexed input to parse from. Returns the item you wanted (or an error message), plus the remainder of the input.
Individual parsers for use with xmlParseWith and module SAX
document :: XParser (Document Posn) Source #
Return an entire XML document including prolog and trailing junk.
element :: XParser (Element Posn) Source #
Return a complete element including all its inner content.
content :: XParser (Content Posn) Source #
Return a content particle, e.g. text, element, reference, etc
reference :: XParser Reference Source #
Return either a general entity reference, or a character reference.
doctypedecl :: XParser DocTypeDecl Source #
Return a DOCTYPE decl, indicating a DTD.
processinginstruction :: XParser ProcessingInstruction Source #
Parse a processing instruction.
qname :: XParser QName Source #
Return a qualified name (although the namespace qualification is not processed here; this is merely to get the correct type).
tok :: TokenT -> XParser TokenT Source #
Return the next token from the input only if it matches the given token.
elemOpenTag :: XParser ElemTag Source #
For use with stream parsers - returns the complete opening element tag.
elemCloseTag :: QName -> XParser () Source #
For use with stream parsers - accepts a closing tag, provided it matches the given element name.
type XParser a = Parser SymTabs (Posn, TokenT) a Source #
XParser is just a specialisation of the PolyState parser.