- document :: Document i -> Doc
- mkXMLDocument :: Element () -> Document ()
- mkPlanBundle :: [Element ()] -> Element ()
- serializeAlgebra :: [Element ()] -> GraphNode -> XML XMLNode
- type ColName = String
- type Graph = (AlgNode, [(Algebra, AlgNode)])
- type GraphNode = Int
- type XMLNode = Int
- type Dictionary = Map GraphNode XMLNode
- type XML = WriterT [Element ()] (ReaderT (Map AlgNode Algebra, Map AlgNode [String], Bool) (State (Int, Dictionary)))
- getTags :: GraphNode -> XML (Maybe [String])
- debugEnabled :: XML Bool
- isDefined :: GraphNode -> XML (Maybe XMLNode)
- freshId :: XML Int
- addNodeTrans :: GraphNode -> XMLNode -> XML ()
- getNode :: Int -> XML Algebra
- runXML :: Bool -> Map AlgNode Algebra -> Map AlgNode [String] -> XML a -> [Element ()]
- childsOf :: [Element ()] -> Element () -> Element ()
- dataChildOf :: Show a => a -> Element () -> Element ()
- stringChildOf :: String -> Element () -> Element ()
- column :: String -> Bool -> Element ()
- typeN :: ATy -> Element ()
- xmlElem :: String -> Element ()
- node :: XMLNode -> String -> Element ()
- contentNode :: Element ()
- attr :: String -> String -> Attribute
- attrsOf :: [Attribute] -> Element () -> Element ()
- module Text.XML.HaXml.Types
- iterCol :: Element ()
- posCol :: Element ()
- mkQueryPlan :: Maybe (Int, Int) -> Element () -> [Element ()] -> XML Int
Documentation
type Dictionary = Map GraphNode XMLNodeSource
type XML = WriterT [Element ()] (ReaderT (Map AlgNode Algebra, Map AlgNode [String], Bool) (State (Int, Dictionary)))Source
Helper functions for constructing xml nodes
childsOf :: [Element ()] -> Element () -> Element ()Source
Childs of takes a list of xml elements, and nests them in the xml element given as a second argument
dataChildOf :: Show a => a -> Element () -> Element ()Source
Data child of takes some data that can be printed and adds that as child to the xml element given as second argument
contentNode :: Element ()Source
Construct a content node
attr :: String -> String -> AttributeSource
Construct an attribute for an xml node, attrname = n and its value is v
module Text.XML.HaXml.Types