Safe Haskell | None |
---|---|
Language | Haskell98 |
Text.XML.HXQ.XQuery
Contents
- The XML Data Representation
- The XQuery Compiler
- The XQuery Interpreter
- The XQuery Command Line Interpreter
- Validation using XML Schema
- The XQuery Compiler with Database Connectivity
- The XQuery Interpreter with Database Connectivity
- Shredding and Publishing XML Documents Using a Relational Database
- Other Database 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/.
- type Prefix = String
- type URI = String
- type LocalName = String
- data QName = QName {}
- type Attributes = [(QName, String)]
- data XTree
- type XSeq = [XTree]
- type TVar = Int
- type TQualifier = Char
- data Type
- putXSeq :: XSeq -> IO ()
- xq :: String -> Q Exp
- xe :: String -> Q Exp
- qx :: QuasiQuoter
- xquery :: String -> IO XSeq
- eval :: XSeq -> IO XSeq
- commandLineInterpreter :: [String] -> IO ()
- validateFile :: FilePath -> FilePath -> IO Bool
- xqdb :: String -> Q Exp
- xqueryDB :: String -> Connection -> IO XSeq
- type Path = [String]
- data Table
- 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 qualified name has a namespace prefix, a URI, and a local name
type Attributes = [(QName, String)] Source
XML attributes are bindings from qualified names to values
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 !QName !Attributes !Int XTree [XTree] | an XML tree node (element) |
XAttr !QName !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 String String | processing instruction |
XGERef String | general entity reference |
XComment String | comment |
XError String | error message |
XNull | null value |
XType Type | type information |
XNoPad | marker for no padding in XSeq |
type TQualifier = Char Source
Type qualifier: *, +, or ?
An XQuery type
Constructors
TVariable !TVar | type variable (needed for polymorphic type inference) |
TBase !QName | xs:integer, xs:string, ... |
TItem !String | item(), node(), ... |
TNamed !QName | reference to a user-defined type |
TElement !String !Type | element tag { t } |
TAttribute !String !Type | attribute name { t } |
TAny | any element or attribute content |
TEmpty | () |
TSequence !Type !Type | t1, t2 |
TInterleaving !Type !Type | t1 & t2 |
TChoice !Type !Type | t1 | t2 |
TQualified !Type !TQualifier | t*, t+, or t? |
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
.
qx :: QuasiQuoter Source
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 Command Line Interpreter
The XQuery command line interpreter used by the main program (xquery
).
The program arguments may contain the following command line options:
xquery-file
- Evaluate the XQuery code in
xquery-file
using the interpreter -db database-name
- Use the relational schema
database-name
during querying -c xquery-file
- Compile the XQuery code in
xquery-file
into Haskell code -o haskell-file
- Set the Haskell file for
-c
(default isTemp.hs
) -p XPath-query xml-file
- Interpret the XPath query against the
xml-file
-v
- Print verbose information (the AST and the optimized plan)
-t
- Print timing information
-tp
- Print typing information (experimental)
Without an xquery-file
, it reads and evaluates the input using the HXQ interpreter.
The input may be a single XQuery or a declare variable
or a declare function
expression.
To write an XQuery in multiple lines, wrap it in { }
.
Validation using XML Schema
validateFile :: FilePath -> FilePath -> IO Bool Source
Validate the XML document against the XML Schema. Also done using the validate XQuery form.
The XQuery Compiler with Database Connectivity
xqdb :: String -> Q Exp Source
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 XSeq Source
Evaluate the XQuery with database connectivity using the interpreter.
Shredding and Publishing XML Documents Using a Relational Database
A relational schema representation
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 Database Functions
Arguments
:: Connection | database connection |
-> IO () |
Disconnect from the relational database