Text.XML.HXQ.XQuery
Contents
Description
HXQ is a fast and space-efficient compiler from XQuery (the standard query language for XML) to embedded Haskell code. The translation is based on Haskell templates. It also provides an interpreter for evaluating ad-hoc XQueries read from input or from files and optional database connectivity using HDBC. For more information, look at http://lambda.uta.edu/HXQ/.
- type Name = String
- type AttList = [(Name, String)]
- data XTree
- type XSeq = [XTree]
- putXSeq :: XSeq -> IO ()
- xq :: String -> Q Exp
- xe :: String -> Q Exp
- qx :: QuasiQuoter
- xquery :: String -> IO XSeq
- eval :: XSeq -> IO XSeq
- xqdb :: String -> Q Exp
- xqueryDB :: String -> Connection -> IO XSeq
- genSchema :: Connection -> FilePath -> String -> [String] -> IO Table
- shred :: Connection -> FilePath -> String -> IO ()
- shredC :: String -> FilePath -> String -> Q Exp
- isSchema :: Connection -> String -> IO Bool
- printSchema :: Connection -> String -> IO ()
- createIndex :: Connection -> String -> String -> IO ()
- connect :: String -> IO Connection
- disconnect :: Connection -> IO ()
- commit :: Connection -> IO ()
- rollback :: Connection -> IO ()
The XML Data Representation
A rose tree representation of XML data.
An XML element is: XElem tagname atributes preorder parent children.
The preorder numbering is the document order of elements.
The parent is a cyclic reference to the parent element.
Constructors
| XElem !Name !AttList !Int XTree [XTree] | an XML tree node (element) |
| XAttr !Name !String | attribute construction |
| XText !String | an XML tree leaf (PCDATA) |
| XInt !Int | an XML tree leaf (int) |
| XFloat !Double | an XML tree leaf (double) |
| XBool !Bool | an XML tree leaf (boolean) |
| XPI Name String | processing instruction |
| XGERef String | general entity reference |
| XComment String | comment |
| XError String | error report |
| XNull | null value |
| XType Ast | type information |
| XNoPad | marker for no padding in XSeq |
putXSeq :: XSeq -> IO ()Source
Print the XQuery result (which is a sequence of XML fragments) without buffering.
The XQuery Compiler
Compile an XQuery that may perform IO (such as reading an XML document or calling a user function).
When the compiled code is evaluated, it returns a value of type IO XSeq.
Compile an XQuery expression that does not perform IO.
When the compiled code is evaluated, it returns a value of type XSeq.
Quasi-quotation for HXQ (for ghc 6.09 or later). For example, [qx| doc("data/cs.xml")//gpa |] is equivalent to xq "doc(\"data/cs.xml\")//gpa".
The XQuery Interpreter
The XQuery Compiler with Database Connectivity
Compile an XQuery that may perform IO and/or queries a database.
When the compiled code is evaluated, it returns Connection -> IO XSeq.
The XQuery Interpreter with Database Connectivity
xqueryDB :: String -> Connection -> IO XSeqSource
Evaluate the XQuery with database connectivity using the interpreter.
Shredding and Publishing XML Documents Using a Relational Database
Arguments
| :: Connection | database connection |
| -> FilePath | XML document pathname |
| -> String | schema name |
| -> [String] | excluded tags |
| -> IO Table |
Create a schema for an XML document into the database under the given name. The excluded tags are HTML tags to be ignored
Arguments
| :: Connection | database connection |
| -> FilePath | XML document pathname |
| -> String | schema name |
| -> IO () |
Store an XML document into the database under the given name.
Store an XML document into the database under the given name. Generates Haskell code. It's 3 times faster than shred.
True if there is a relational schema stored in the database under the given name
Print the relational schema stored in the database under the given name
Arguments
| :: Connection | database connection |
| -> String | schema name |
| -> String | the tag name of the elements to be indexed |
| -> IO () |
Create a secondary index on tagname for the shredded document under the given name..
Other Functions
Disconnect from the relational database