HXQ-0.17.0: A Compiler from XQuery to HaskellSource codeContentsIndex
Text.XML.HXQ.XQuery
Contents
The XML Data Representation
The XQuery Compiler
The XQuery Interpreter
The XQuery Compiler with Database Connectivity
The XQuery Interpreter with Database Connectivity
Shredding and Publishing XML Documents Using a Relational Database
Other Functions
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/.
Synopsis
type Name = String
type AttList = [(Name, String)]
data XTree
= XElem !Name !AttList !Int XTree [XTree]
| XAttr !Name !String
| XText !String
| XInt !Int
| XFloat !Double
| XBool !Bool
| XPI Name String
| XGERef String
| XComment String
| XError String
| XNull
| XType Ast
| XNoPad
type XSeq = [XTree]
putXSeq :: XSeq -> IO ()
xq :: String -> Q Exp
xe :: String -> Q Exp
qx
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
type Name = StringSource
Element tagname or attribute name
type AttList = [(Name, String)]Source
Attribute list
data XTree Source
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 !Stringattribute construction
XText !Stringan XML tree leaf (PCDATA)
XInt !Intan XML tree leaf (int)
XFloat !Doublean XML tree leaf (double)
XBool !Boolan XML tree leaf (boolean)
XPI Name Stringprocessing instruction
XGERef Stringgeneral entity reference
XComment Stringcomment
XError Stringerror report
XNullnull value
XType Asttype information
XNoPadmarker for no padding in XSeq
show/hide Instances
type XSeq = [XTree]Source
A sequence of XML fragments
putXSeq :: XSeq -> IO ()Source
Print the XQuery result (which is a sequence of XML fragments) without buffering.
The XQuery Compiler
xq :: String -> Q ExpSource
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.
xe :: String -> Q ExpSource
Compile an XQuery expression that does not perform IO. When the compiled code is evaluated, it returns a value of type XSeq.
qx
The XQuery Interpreter
xquery :: String -> IO XSeqSource
Evaluate the XQuery using the interpreter.
eval :: XSeq -> IO XSeqSource
The XQuery interpreter as an XQuery function.
The XQuery Compiler with Database Connectivity
xqdb :: String -> Q ExpSource
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
genSchemaSource
:: Connectiondatabase connection
-> FilePathXML document pathname
-> Stringschema 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
shredSource
:: Connectiondatabase connection
-> FilePathXML document pathname
-> Stringschema name
-> IO ()
Store an XML document into the database under the given name.
shredCSource
:: Stringdatabase name
-> FilePathXML document pathname
-> Stringschema name
-> Q Exp
Store an XML document into the database under the given name. Generates Haskell code. It's 3 times faster than shred.
isSchemaSource
:: Connectiondatabase connection
-> Stringschema name
-> IO Bool
True if there is a relational schema stored in the database under the given name
printSchemaSource
:: Connectiondatabase connection
-> Stringschema name
-> IO ()
Print the relational schema stored in the database under the given name
createIndexSource
:: Connectiondatabase connection
-> Stringschema name
-> Stringthe 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
connectSource
:: Stringdatabase name
-> IO Connection
Connect to a relational database
disconnectSource
:: Connectiondatabase connection
-> IO ()
Disconnect from the relational database
commitSource
:: Connectiondatabase connection
-> IO ()
commit the updates to the database
rollbackSource
:: Connectiondatabase connection
-> IO ()
rollback the updates from the database
Produced by Haddock version 2.4.2