-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | A collection of tools for processing XML with Haskell. -- -- The Haskell XML Toolbox bases on the ideas of HaXml and HXML, but -- introduces a more general approach for processing XML with Haskell. -- The Haskell XML Toolbox uses a generic data model for representing XML -- documents, including the DTD subset and the document subset, in -- Haskell. It contains a validating XML parser, a HTML parser, namespace -- support, an XPath expression evaluator, an XSLT library, a RelaxNG -- schema validator and funtions for serialization and deserialization of -- user defined data. The library makes extensive use of the arrow -- approach for processing XML. Since version 9 the toolbox is -- partitioned into various (sub-)packages. This package contains the -- core functionality, hxt-curl, hxt-tagsoup, hxt-relaxng, hxt-xpath, -- hxt-xslt, hxt-regex-xmlschema contain the extensions. hxt-unicode -- contains encoding and decoding functions, hxt-charproperties char -- properties for unicode and XML. -- -- Changes from 9.3.1.15: Bug in quoting PI instructions in showXmlTrees -- fixed -- -- Changes from 9.3.1.14: For ghc-7.10 network-uri is automatically -- selected -- -- Changes from 9.3.1.13: ghc-7.10 compatibility -- -- Changes from 9.3.1.12: Bug when unpickling an empty attribute value -- removed -- -- Changes from 9.3.1.11: Bug fix in haddock comments -- -- Changes from 9.3.1.10: Bug in DTD validation, space and time leak in -- delta removed -- -- Changes from 9.3.1.9: lower bound of mtl dependency lowered to 2.0.1 -- -- Changes from 9.3.1.8: Bug in hread removed -- -- Changes from 9.3.1.7: Foldable and Traversable instances for NTree -- added Control.Except used instead of deprecated Control.Error -- -- Changes from 9.3.1.6: canonicalize added in hread and hreadDoc -- -- Changes from 9.3.1.4: conditionally (no default) dependency from -- networt changed to network-uri with flag "network-uri" -- -- Changes from 9.3.1.3: warnings from ghc-7.8.1 removed -- -- Changes from 9.3.1.2: https as protocol added -- -- Changes from 9.3.1.1: new parser xreadDoc -- -- Changes from 9.3.1.0: in readString all input decoding switched off -- -- Changes from 9.3.0.1: lower bound for network set to be >= 2.4 -- -- Changes from 9.3.0: upper bound for network set to be < 2.4 (URI -- signatures changed in 2.4) -- -- Changes from 9.2.2: XMLSchema validation integrated -- -- Changes from 9.2.1: user defined mime type handlers added -- -- Changes from 9.2.0: New warnings from ghc-7.4 removed @package hxt @version 9.3.1.16 -- | Version : $Id$ -- -- Datatype library for the W3C XML schema datatypes module Text.XML.HXT.XMLSchema.DataTypeLibW3CNames -- | Namespace of the W3C XML schema datatype library w3cNS :: String xsd_string :: String xsd_normalizedString :: String xsd_token :: String xsd_language :: String xsd_NMTOKEN :: String xsd_NMTOKENS :: String xsd_Name :: String xsd_NCName :: String xsd_ID :: String xsd_IDREF :: String xsd_IDREFS :: String xsd_ENTITY :: String xsd_ENTITIES :: String xsd_anyURI :: String xsd_QName :: String xsd_NOTATION :: String xsd_hexBinary :: String xsd_base64Binary :: String xsd_decimal :: String xsd_integer :: String xsd_nonPositiveInteger :: String xsd_negativeInteger :: String xsd_nonNegativeInteger :: String xsd_positiveInteger :: String xsd_long :: String xsd_int :: String xsd_short :: String xsd_byte :: String xsd_unsignedLong :: String xsd_unsignedInt :: String xsd_unsignedShort :: String xsd_unsignedByte :: String xsd_boolean :: String xsd_float :: String xsd_double :: String xsd_time :: String xsd_duration :: String xsd_date :: String xsd_dateTime :: String xsd_gDay :: String xsd_gMonth :: String xsd_gMonthDay :: String xsd_gYear :: String xsd_gYearMonth :: String xsd_length :: String xsd_maxLength :: String xsd_minLength :: String xsd_maxExclusive :: String xsd_minExclusive :: String xsd_maxInclusive :: String xsd_minInclusive :: String xsd_totalDigits :: String xsd_fractionDigits :: String xsd_pattern :: String xsd_enumeration :: String xsd_whiteSpace :: String module Text.XML.HXT.Version hxt_version :: String -- | Predefined XML Entity References -- -- This module defines a table of all predefined XML entity references module Text.XML.HXT.Parser.XmlEntities -- | list of predefined XML entity names and their unicode values xmlEntities :: [(String, Int)] -- | UTF-8 character parser and simple XML token parsers module Text.XML.HXT.Parser.XmlCharParser type XParser s a = GenParser Char (XPState s) a type SimpleXParser a = XParser () a data XPState s XPState :: !Bool -> s -> XPState s [xps_normalizeNewline] :: XPState s -> !Bool [xps_userState] :: XPState s -> s withNormNewline :: a -> XPState a withoutNormNewline :: a -> XPState a -- | parse a single Unicode character xmlChar :: XParser s Unicode -- | parse a XML name character xmlNameChar :: XParser s Unicode -- | parse a XML name start character xmlNameStartChar :: XParser s Unicode -- | parse a XML NCName character xmlNCNameChar :: XParser s Unicode -- | parse a XML NCName start character xmlNCNameStartChar :: XParser s Unicode -- | parse a XML letter character xmlLetter :: XParser s Unicode -- | White Space (2.3) -- -- end of line handling (2.11) will be done before or with -- xmlCRLFChar parser xmlSpaceChar :: XParser s Char -- | White Space Normalization -- -- end of line handling (2.11) #x0D and #x0D#x0A are mapped to #x0A xmlCRLFChar :: XParser s Char -- | XHTML Entity References -- -- This module defines a table of all predefined XHTML entity references -- for special or none ASCII chars including the predefined XML entity -- refs module Text.XML.HXT.Parser.XhtmlEntities -- | table with all XHTML entity refs and corresponding unicode values xhtmlEntities :: [(String, Int)] -- | A module for regular expression matching based on derivatives of -- regular expressions. -- -- The code was taken from Joe English -- (http://www.flightlab.com/~joe/sgml/validate.html). Tested and -- extended by Martin Schmidt. -- -- Further references for the algorithm: -- -- Janusz A. Brzozowski. -- -- Derivatives of Regular Expressions. Journal of the ACM, Volume 11, -- Issue 4, 1964. -- -- Mark Hopkins. -- -- Regular Expression Package. Posted to comp.compilers, 1994. Available -- per FTP at ftp://iecc.com/pub/file/regex.tar.gz. module Text.XML.HXT.DTDValidation.RE -- | Data type for regular expressions. data RE a RE_ZERO :: String -> RE a RE_UNIT :: RE a RE_SYM :: a -> RE a RE_DOT :: RE a RE_REP :: (RE a) -> RE a RE_PLUS :: (RE a) -> RE a RE_OPT :: (RE a) -> RE a RE_SEQ :: (RE a) -> (RE a) -> RE a RE_ALT :: (RE a) -> (RE a) -> RE a -- | Constructs a regular expression for an empty sequence. -- -- re_unit :: RE a -- | Constructs a regular expression for an empty set. -- -- re_zero :: String -> RE a -- | Constructs a regular expression for accepting a symbol -- -- re_sym :: a -> RE a -- | Constructs an optional repetition (*) of a regular expression -- -- re_rep :: RE a -> RE a -- | Constructs a repetition (+) of a regular expression -- -- re_plus :: RE a -> RE a -- | Constructs an option (?) of a regular expression -- -- re_opt :: (Ord a) => RE a -> RE a -- | Constructs a sequence (,) of two regular expressions -- -- re_seq :: RE a -> RE a -> RE a -- | Constructs an alternative (|) of two regular expressions -- -- re_alt :: (Ord a) => RE a -> RE a -> RE a -- | Constructs a regular expression for accepting any singel symbol -- -- re_dot :: RE a -- | Checks if an input matched a regular expression. The function should -- be called after matches. -- -- Was the sentence used in matches in the language of the -- regular expression? -> matches e s == s `in` L(e)? -- -- checkRE :: (Eq a, Show a) => RE a -> String -- | Derives a regular expression with respect to a sentence. -- -- matches :: (Ord a, Show a) => RE a -> [a] -> RE a -- | Checks if a regular expression matches the empty sequence. -- -- nullable e == [] `in` L(e) -- -- This check indicates if a regular expression fits to a sentence or -- not. -- -- nullable :: RE a -> Bool -- | Constructs a string representation of a regular expression. -- -- printRE :: (Eq a, Show a) => RE a -> String instance GHC.Classes.Ord a => GHC.Classes.Ord (Text.XML.HXT.DTDValidation.RE.RE a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Text.XML.HXT.DTDValidation.RE.RE a) instance GHC.Show.Show a => GHC.Show.Show (Text.XML.HXT.DTDValidation.RE.RE a) -- | Constants for XML keywords, for special attribute names and special -- attribute values module Text.XML.HXT.DOM.XmlKeywords t_xml :: String t_root :: String a_default :: String a_contentLength :: String a_column :: String a_encoding :: String a_kind :: String a_line :: String a_module :: String a_modifier :: String a_name :: String a_output_encoding :: String a_peref :: String a_source :: String a_status :: String a_standalone :: String a_type :: String a_url :: String a_value :: String a_version :: String a_xml :: String a_xmlns :: String v_0 :: String v_1 :: String v_2 :: String v_yes :: String v_no :: String v_any :: String v_children :: String v_choice :: String v_empty :: String v_mixed :: String v_seq :: String v_null :: String v_option :: String v_pcdata :: String v_star :: String v_plus :: String k_any :: String k_cdata :: String k_empty :: String k_entity :: String k_entities :: String k_id :: String k_idref :: String k_idrefs :: String k_include :: String k_ignore :: String k_nmtoken :: String k_nmtokens :: String k_peref :: String k_public :: String k_system :: String k_enumeration :: String k_fixed :: String k_implied :: String k_ndata :: String k_notation :: String k_pcdata :: String k_required :: String k_default :: String dtdPrefix :: String transferPrefix :: String transferProtocol :: String transferMimeType :: String transferEncoding :: String transferURI :: String transferDefaultURI :: String transferStatus :: String transferMessage :: String transferVersion :: String httpPrefix :: String stringProtocol :: String -- | the predefined namespace uri for xml: -- "http://www.w3.org/XML/1998/namespace" xmlNamespace :: String -- | the predefined namespace uri for xmlns: -- "http://www.w3.org/2000/xmlns/" xmlnsNamespace :: String -- | Relax NG namespace relaxNamespace :: String -- | The GET method for file protocol module Text.XML.HXT.IO.GetFILE getStdinCont :: Bool -> IO (Either ([(String, String)], String) ByteString) getCont :: Bool -> String -> IO (Either ([(String, String)], String) ByteString) -- | Little useful things for strings, lists and other values module Text.XML.HXT.DOM.Util -- | remove leading and trailing whitespace with standard Haskell predicate -- isSpace stringTrim :: String -> String -- | convert string to lowercase with standard Haskell toLower function stringToLower :: String -> String -- | convert string to uppercase with standard Haskell toUpper function stringToUpper :: String -> String -- | find all positions where a string occurs within another string stringAll :: (Eq a) => [a] -> [a] -> [Int] -- | find the position of the first occurence of a string stringFirst :: (Eq a) => [a] -> [a] -> Maybe Int -- | find the position of the last occurence of a string stringLast :: (Eq a) => [a] -> [a] -> Maybe Int -- | Removes leading / trailing whitespaces and leading zeros normalizeNumber :: String -> String -- | Reduce whitespace sequences to a single whitespace normalizeWhitespace :: String -> String -- | replace all whitespace chars by blanks normalizeBlanks :: String -> String -- | Escape all disallowed characters in URI references (see -- http://www.w3.org/TR/xlink/#link-locators) escapeURI :: String -> String -- | escape XML chars &lt; and ampercent by transforming them into -- character references, used for escaping text nodes -- -- see also : attrEscapeXml textEscapeXml :: String -> String -- | escape XML chars &lt;, &gt;, &quot;, and ampercent by -- transforming them into character references -- -- see also : attrEscapeXml stringEscapeXml :: String -> String -- | escape XML chars in attribute values, same as stringEscapeXml, but -- none blank whitespace is also escaped -- -- see also : stringEscapeXml attrEscapeXml :: String -> String stringToInt :: Int -> String -> Int -- | convert a string into a hexadecimal string applying charToHexString -- -- see also : charToHexString stringToHexString :: String -> String -- | convert a char (byte) into a 2-digit hexadecimal string -- -- see also : stringToHexString, intToHexString charToHexString :: Char -> String -- | convert a none negative Int into a hexadecimal string -- -- see also : charToHexString intToHexString :: Int -> String -- | convert a string of hexadecimal digits into an Int hexStringToInt :: String -> Int -- | convert a string of digits into an Int decimalStringToInt :: String -> Int -- | take all elements of a list which occur more than once. The result -- does not contain doubles. (doubles . doubles == doubles) doubles :: Eq a => [a] -> [a] -- | drop all elements from a list which occur more than once. singles :: Eq a => [a] -> [a] -- | remove duplicates from list noDoubles :: Eq a => [a] -> [a] swap :: (a, b) -> (b, a) partitionEither :: [Either a b] -> ([a], [b]) toMaybe :: Bool -> a -> Maybe a -- | mothers little helpers for to much curry uncurry3 :: (a -> b -> c -> d) -> (a, b, c) -> d uncurry4 :: (a -> b -> c -> d -> e) -> (a, b, c, d) -> e module Text.XML.HXT.Parser.ProtocolHandlerUtil -- | Try to extract charset spec from Content-Type header e.g. "text/html; -- charset=ISO-8859-1" -- -- Sometimes the server deliver the charset spec in quotes these are -- removed parseContentType :: Parser [(String, String)] -- | default mime type table -- -- this file is generated from file etcmime.types module Text.XML.HXT.DOM.MimeTypeDefaults -- | the table with the mapping from file name extensions to mime types mimeTypeDefaults :: [(String, String)] -- | mime type related data and functions module Text.XML.HXT.DOM.MimeTypes type MimeTypeTable = Map String String application_xhtml :: String application_xml :: String application_xml_external_parsed_entity :: String application_xml_dtd :: String text_html :: String text_pdf :: String text_plain :: String text_xdtd :: String text_xml :: String text_xml_external_parsed_entity :: String isTextMimeType :: String -> Bool isHtmlMimeType :: String -> Bool isXmlMimeType :: String -> Bool defaultMimeTypeTable :: MimeTypeTable extensionToMimeType :: String -> MimeTypeTable -> String readMimeTypeTable :: FilePath -> IO MimeTypeTable parseMimeTypeTable :: String -> [(String, String)] -- | Interface definition for navigatable trees. Navigatable trees need to -- have operations to move up, down, left and right. With these -- elementary operations, most of the XPath axises can be defined. module Data.Tree.NavigatableTree.Class -- | The interface for navigatable trees class NavigatableTree t -- | move one step towards the root mvUp :: NavigatableTree t => t a -> Maybe (t a) -- | descend one step to the leftmost child mvDown :: NavigatableTree t => t a -> Maybe (t a) -- | move to the left neighbour mvLeft :: NavigatableTree t => t a -> Maybe (t a) -- | move to the right neighbour mvRight :: NavigatableTree t => t a -> Maybe (t a) -- | Conversion between trees and navigatable trees, -- -- There is only a single navigatable tree implementation for a given -- tree allowed (see the functional dependencies) class NavigatableTreeToTree nt t | t -> nt, nt -> t -- | construct a navigatable tree fromTree :: NavigatableTreeToTree nt t => t a -> nt a -- | remove navigation toTree :: NavigatableTreeToTree nt t => nt a -> t a -- | Edit operation on navigatable trees -- -- There is only a single navigatable tree implementation for a given -- tree allowed (see the functional dependencies) class NavigatableTreeModify nt t | t -> nt, nt -> t -- | add an ordinary tree in front of the given navigatable tree addTreeLeft :: NavigatableTreeModify nt t => t a -> nt a -> Maybe (nt a) -- | add an ordinary tree behind of the given navigatable tree addTreeRight :: NavigatableTreeModify nt t => t a -> nt a -> Maybe (nt a) -- | drop the direct left sibling tree of the given navigatable tree dropTreeLeft :: NavigatableTreeModify nt t => nt a -> Maybe (nt a) -- | drop the direct right sibling tree of the given navigatable tree dropTreeRight :: NavigatableTreeModify nt t => nt a -> Maybe (nt a) -- | change the tree but remain the navigation substThisTree :: NavigatableTreeModify nt t => t a -> nt a -> nt a -- | Navigatable trees need to have operations to move up, down, left and -- right. With these elementary operations, the XPath axises can be -- defined. module Data.Tree.NavigatableTree.XPathAxis -- | collect all trees by moving into one direction, starting tree is -- included maybeStar :: (a -> Maybe a) -> (a -> [a]) -- | collect all trees by moving into one direction, starting tree is not -- included maybePlus :: (a -> Maybe a) -> (a -> [a]) -- | XPath axis: parent parentAxis :: NavigatableTree t => t a -> [t a] -- | XPath axis: ancestor ancestorAxis :: NavigatableTree t => t a -> [t a] -- | XPath axis: ancestor or self ancestorOrSelfAxis :: NavigatableTree t => t a -> [t a] -- | XPath axis: child childAxis :: NavigatableTree t => t a -> [t a] -- | XPath axis: descendant descendantAxis :: NavigatableTree t => t a -> [t a] -- | XPath axis: descendant or self descendantOrSelfAxis :: NavigatableTree t => t a -> [t a] -- | not an official XPath axis but useful: reverse descendant or self, -- used in preceding axis revDescendantOrSelfAxis :: NavigatableTree t => t a -> [t a] -- | XPath axis: following sibling followingSiblingAxis :: NavigatableTree t => t a -> [t a] -- | XPath axis: preceeding sibling precedingSiblingAxis :: NavigatableTree t => t a -> [t a] -- | XPath axis: self selfAxis :: NavigatableTree t => t a -> [t a] -- | XPath axis: following followingAxis :: NavigatableTree t => t a -> [t a] -- | XPath axis: preceding precedingAxis :: NavigatableTree t => t a -> [t a] -- | move to the root mvToRoot :: NavigatableTree t => t a -> t a isAtRoot :: NavigatableTree t => t a -> Bool -- | Interface definition for trees module Data.Tree.Class -- | The interface for trees class Tree t where mkLeaf n = mkTree n [] isLeaf = null . getChildren isInner = not . isLeaf setNode n = changeNode (const n) setChildren cl = changeChildren (const cl) nodesTree = foldTree (\ n rs -> n : concat rs) depthTree = foldTree (\ _ rs -> 1 + maximum (0 : rs)) cardTree = foldTree (\ _ rs -> 1 + sum rs) formatTree nf n = formatNTree' nf (showString "---") (showString " ") n "" -- | tree construction: a new tree is constructed by a node attribute and a -- list of children mkTree :: Tree t => a -> [t a] -> t a -- | leaf construction: leafs don't have any children -- -- definition: mkLeaf n = mkTree n [] mkLeaf :: Tree t => a -> t a -- | leaf test: list of children empty? isLeaf :: Tree t => t a -> Bool -- | innner node test: not . isLeaf isInner :: Tree t => t a -> Bool -- | select node attribute getNode :: Tree t => t a -> a -- | select children getChildren :: Tree t => t a -> [t a] -- | edit node attribute changeNode :: Tree t => (a -> a) -> t a -> t a -- | edit children changeChildren :: Tree t => ([t a] -> [t a]) -> t a -> t a -- | substitute node: setNode n = changeNode (const n) setNode :: Tree t => a -> t a -> t a -- | substitute children: setChildren cl = changeChildren (const cl) -- setChildren :: Tree t => [t a] -> t a -> t a -- | fold for trees foldTree :: Tree t => (a -> [b] -> b) -> t a -> b -- | all nodes of a tree nodesTree :: Tree t => t a -> [a] -- | depth of a tree depthTree :: Tree t => t a -> Int -- | number of nodes in a tree cardTree :: Tree t => t a -> Int -- | format tree for readable trace output -- -- a graphical representation of the tree in text format formatTree :: Tree t => (a -> String) -> t a -> String -- | convert a tree into a pseudo graphical string representation formatNTree' :: Tree t => (a -> String) -> (String -> String) -> (String -> String) -> t a -> String -> String module Data.Function.Selector -- | A Selector is a pair of an access function and a modifying function -- for reading and updating parts of a composite type data Selector s a S :: (s -> a) -> (a -> s -> s) -> Selector s a [getS] :: Selector s a -> s -> a [setS] :: Selector s a -> a -> s -> s chgS :: Selector s a -> (a -> a) -> (s -> s) chgM :: (Monad m) => Selector s a -> (a -> m a) -> (s -> m s) -- | Alias for constructor S mkSelector :: (s -> a) -> (a -> s -> s) -> Selector s a idS :: Selector s s (.&&&.) :: Selector s a -> Selector s b -> Selector s (a, b) infixr 3 .&&&. -- | Selectors for pairs and 3-tuples: comp1, comp2, comp3, this can be -- extended to n-tuples class Comp1 s a | s -> a comp1 :: Comp1 s a => Selector s a class Comp2 s a | s -> a comp2 :: Comp2 s a => Selector s a class Comp3 s a | s -> a comp3 :: Comp3 s a => Selector s a instance Control.Category.Category Data.Function.Selector.Selector instance Data.Function.Selector.Comp1 (a, b) a instance Data.Function.Selector.Comp2 (a, b) b instance Data.Function.Selector.Comp1 (a, b, c) a instance Data.Function.Selector.Comp2 (a, b, c) b instance Data.Function.Selector.Comp3 (a, b, c) c -- | Unique Atoms generated from Strings and managed as flyweights -- -- Data.Atom can be used for caching and storage optimisation of -- frequently used strings. An Atom is constructed from a -- String. For two equal strings the identical atom is returned. -- -- This module can be used for optimizing memory usage when working with -- strings or names. Many applications use data types like Map String -- SomeAttribute where a rather fixed set of keys is used. -- Especially XML applications often work with a limited set of element -- and attribute names. For these applications it becomes more memory -- efficient when working with types like Map Atom SomeAttribute -- and convert the keys into atoms before operating on such a map. -- -- Internally this module manages a map of atoms. The atoms are -- internally represented by ByteStrings. When creating a new -- atom from a string, the string is first converted into an UTF8 -- Word8 sequence, which is packed into a ByteString. -- This ByteString is looked up in the table of atoms. If it is -- already there, the value in the map is used as atom, else the new -- ByteString is inserted into the map. -- -- Of course the implementation of this name cache uses -- unsavePerformIO. The global cache is managed by ue of an -- IORef and atomicModifyIORef. -- -- The following laws hold for atoms -- --
--   s  ==       t => newAtom s  ==       newAtom t
--   s `compare` t => newAtom s `compare` newAtom t
--   show . newAtom == id
--   
-- -- Equality test for Atoms runs in O(1), it is just a -- pointer comarison. The Ord comparisons have the same runtime -- like the ByteString comparisons. Internally there is an UTF8 -- comparison, but UTF8 encoding preserves the total order. -- -- Warning: The internal cache never shrinks during execution. So using -- it in a undisciplined way can lead to memory leaks. module Data.Atom data Atom -- | creation of an Atom from a String newAtom :: String -> Atom -- | Insert a String into the atom cache and convert the atom back -- into a String. -- -- locically share == id holds, but internally equal strings -- share the same memory. share :: String -> String instance GHC.Classes.Eq Data.Atom.Atom instance GHC.Classes.Ord Data.Atom.Atom instance GHC.Read.Read Data.Atom.Atom instance GHC.Show.Show Data.Atom.Atom instance Control.DeepSeq.NFData Data.Atom.Atom -- | Simple key value assocciation list implemented as unordered list of -- pairs module Data.AssocList type AssocList k v = [(k, v)] -- | lookup with default value lookupDef :: Eq k => v -> k -> AssocList k v -> v -- | lookup with empty list (empty string) as default value lookup1 :: Eq k => k -> AssocList k [e] -> [e] -- | test for existence of a key hasEntry :: Eq k => k -> AssocList k v -> Bool -- | add an entry, remove an existing entry before adding the new one at -- the top of the list, addEntry is strict addEntry :: Eq k => k -> v -> AssocList k v -> AssocList k v -- | add a whole list of entries with addEntry addEntries :: Eq k => AssocList k v -> AssocList k v -> AssocList k v -- | delete an entry, delEntry is strict delEntry :: Eq k => k -> AssocList k v -> AssocList k v -- | delete a list of entries with delEntry delEntries :: Eq k => [k] -> AssocList k v -> AssocList k v -- | Force evaluation like deepseq in Control.DeepSeq, but control the -- depth of evaluation. flatseq may evaluate more than seq but less than -- deepseq module Control.FlatSeq ($!!) :: WNFData a => (a -> b) -> a -> b infixr 0 $!! flatseq :: WNFData a => a -> b -> b rlnf :: (a -> ()) -> [a] -> () -- | A class of types that can be partially evaluated, but evaluation can -- be propagated deeper than WHNF class WNFData a where rwnf a = a `seq` () rwnf2 = rwnf -- | Default for rwnf is reduction to WHNF rwnf :: WNFData a => a -> () -- | Default for rwnf2 is rwnf rwnf2 :: WNFData a => a -> () instance Control.FlatSeq.WNFData GHC.Types.Int instance Control.FlatSeq.WNFData GHC.Integer.Type.Integer instance Control.FlatSeq.WNFData GHC.Types.Float instance Control.FlatSeq.WNFData GHC.Types.Double instance Control.FlatSeq.WNFData GHC.Types.Char instance Control.FlatSeq.WNFData GHC.Types.Bool instance Control.FlatSeq.WNFData () instance Control.FlatSeq.WNFData GHC.Types.Word instance Control.FlatSeq.WNFData GHC.Word.Word8 instance Control.FlatSeq.WNFData GHC.Word.Word16 instance Control.FlatSeq.WNFData GHC.Word.Word32 instance Control.FlatSeq.WNFData GHC.Word.Word64 instance Control.FlatSeq.WNFData a => Control.FlatSeq.WNFData [a] instance (Control.FlatSeq.WNFData a, Control.FlatSeq.WNFData b) => Control.FlatSeq.WNFData (a, b) instance (Control.FlatSeq.WNFData a, Control.FlatSeq.WNFData b, Control.FlatSeq.WNFData c) => Control.FlatSeq.WNFData (a, b, c) instance (Control.FlatSeq.WNFData a, Control.FlatSeq.WNFData b, Control.FlatSeq.WNFData c, Control.FlatSeq.WNFData d) => Control.FlatSeq.WNFData (a, b, c, d) -- | Interface definition for trees -- -- n-ary tree structure (rose trees) module Data.Tree.NTree.TypeDefs -- | n-ary ordered tree (rose trees) -- -- a tree consists of a node and a possible empty list of children. If -- the list of children is empty, the node is a leaf, else it's an inner -- node. -- -- NTree implements Eq, Ord, Show and Read data NTree a NTree :: a -> (NTrees a) -> NTree a -- | shortcut for a sequence of n-ary trees type NTrees a = [NTree a] -- | NTree implements class Functor -- | NTree implements class Foldable -- | NTree implements class Taversable -- | Implementation of Data.Tree.Class interface for rose trees instance GHC.Read.Read a => GHC.Read.Read (Data.Tree.NTree.TypeDefs.NTree a) instance GHC.Show.Show a => GHC.Show.Show (Data.Tree.NTree.TypeDefs.NTree a) instance GHC.Classes.Ord a => GHC.Classes.Ord (Data.Tree.NTree.TypeDefs.NTree a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Data.Tree.NTree.TypeDefs.NTree a) instance Control.DeepSeq.NFData a => Control.DeepSeq.NFData (Data.Tree.NTree.TypeDefs.NTree a) instance Control.FlatSeq.WNFData a => Control.FlatSeq.WNFData (Data.Tree.NTree.TypeDefs.NTree a) instance Data.Binary.Class.Binary a => Data.Binary.Class.Binary (Data.Tree.NTree.TypeDefs.NTree a) instance GHC.Base.Functor Data.Tree.NTree.TypeDefs.NTree instance Data.Foldable.Foldable Data.Tree.NTree.TypeDefs.NTree instance Data.Traversable.Traversable Data.Tree.NTree.TypeDefs.NTree instance Data.Tree.Class.Tree Data.Tree.NTree.TypeDefs.NTree -- | Space and time efficient editing of rose trees module Data.Tree.NTree.Edit -- | editNTreeBottomUp is a space optimized tree edit function -- -- The nodes in a tree are visited bottom up. An edit function is applied -- to all nodes. A Nothing result of the editing function indicates no -- changes. This is used to share the input tree within the resulting -- tree. -- -- The following law holds: -- --
--   editNTreeBottomUp (const Nothing) t == [t]
--   
-- -- In this case the resulting tree does not only represent the same value -- but it is the same machine value (relative to some evaluations of -- closures during the tree walk -- -- With a simple fold like editing function the whole tree would be -- reconstructed in memory editNTreeBottomUp :: (NTree a -> Maybe [NTree a]) -> NTree a -> [NTree a] -- | A space optimized map for NTrees -- -- Subtrees, that are not changed are reused in the resulting tree See -- also: editNTreeBottomUp mapNTree' :: (a -> Maybe a) -> NTree a -> NTree a -- | Implementation of navigateble trees for rose trees. The implementation -- is done with zippers. A description and introductory tutorial about -- zippers can be found in http://learnyouahaskell.com/zippers module Data.Tree.NTree.Zipper.TypeDefs -- | Zipper for rose trees -- -- A zipper consist of the current tree and the branches on the way back -- to the root data NTZipper a NTZ :: (NTree a) -> (NTBreadCrumbs a) -> NTZipper a [ntree] :: NTZipper a -> (NTree a) [context] :: NTZipper a -> (NTBreadCrumbs a) -- | The list of unzipped nodes from a current tree back to the root type NTBreadCrumbs a = [NTCrumb a] -- | One unzipped step consists of the left siblings, the node info and the -- right siblings data NTCrumb a NTC :: (NTrees a) -> a -> (NTrees a) -> NTCrumb a -- | Conversion of a rose tree into a navigatable rose tree toNTZipper :: NTree a -> NTZipper a -- | Conversion of a navigatable rose tree into an ordinary rose tree. -- -- The context, the parts for moving up to the root are just removed from -- the tree. So when transforming a navigatable tree by moving around and -- by changing some nodes, one has to navigate back to the root, else -- that parts are removed from the result fromNTZipper :: NTZipper a -> NTree a up :: NTZipper a -> Maybe (NTZipper a) down :: NTZipper a -> Maybe (NTZipper a) toTheRight :: NTZipper a -> Maybe (NTZipper a) toTheLeft :: NTZipper a -> Maybe (NTZipper a) addToTheLeft :: NTree a -> NTZipper a -> Maybe (NTZipper a) addToTheRight :: NTree a -> NTZipper a -> Maybe (NTZipper a) dropFromTheLeft :: NTZipper a -> Maybe (NTZipper a) dropFromTheRight :: NTZipper a -> Maybe (NTZipper a) isTop :: NTZipper a -> Bool up1 :: NTree a -> NTCrumb a -> NTree a instance GHC.Show.Show a => GHC.Show.Show (Data.Tree.NTree.Zipper.TypeDefs.NTZipper a) instance GHC.Show.Show a => GHC.Show.Show (Data.Tree.NTree.Zipper.TypeDefs.NTCrumb a) instance GHC.Base.Functor Data.Tree.NTree.Zipper.TypeDefs.NTZipper instance GHC.Base.Functor Data.Tree.NTree.Zipper.TypeDefs.NTCrumb instance Data.Tree.Class.Tree Data.Tree.NTree.Zipper.TypeDefs.NTZipper instance Data.Tree.NavigatableTree.Class.NavigatableTree Data.Tree.NTree.Zipper.TypeDefs.NTZipper instance Data.Tree.NavigatableTree.Class.NavigatableTreeToTree Data.Tree.NTree.Zipper.TypeDefs.NTZipper Data.Tree.NTree.TypeDefs.NTree instance Data.Tree.NavigatableTree.Class.NavigatableTreeModify Data.Tree.NTree.Zipper.TypeDefs.NTZipper Data.Tree.NTree.TypeDefs.NTree -- | The types and functions for qualified names module Text.XML.HXT.DOM.QualifiedName -- | Namespace support for element and attribute names. -- -- A qualified name consists of a name prefix, a local name and a -- namespace uri. All modules, which are not namespace aware, use only -- the localPart component. When dealing with namespaces, the -- document tree must be processed by propagateNamespaces to split -- names of structure "prefix:localPart" and label the name with the -- apropriate namespace uri data QName -- | XML names are represented by Strings, but these strings do not mix up -- with normal strings. Names are always reduced to normal form, and they -- are stored internally in a name cache for sharing equal names by the -- same data structure data XName -- | Type for the namespace association list, used when propagating -- namespaces by modifying the QName values in a tree type NsEnv = AssocList XName XName -- | constructs a complete qualified name with namePrefix, -- localPart and namespaceUri. This function can be used to -- build not wellformed prefix:localpart names. The XPath module uses -- wildcard names like xxx:*. These must be build with -- mkQName and not with mkName. mkQName :: String -> String -> String -> QName -- | constructs a simple, namespace unaware name. If the name is in -- prefix:localpart form and the prefix is not empty the name is -- split internally into a prefix and a local part. mkName :: String -> QName -- | constructs a simple, namespace aware name, with prefix:localPart as -- first parameter, namspace uri as second. -- -- see also mkName, mkPrefixLocalPart mkNsName :: String -> String -> QName -- | old name for mkName -- | Deprecated: use mkName instead mkSNsName :: String -> QName -- | constructs a simple name, with prefix and localPart but without a -- namespace uri. -- -- see also mkQName, mkName mkPrefixLocalPart :: String -> String -> QName -- | Equivalent QNames are defined as follows: The URIs are normalized -- before comparison. Comparison is done with equalQNameBy and -- equivUri equivQName :: QName -> QName -> Bool -- | Comparison of normalized namespace URIs using normalizeNsUri equivUri :: String -> String -> Bool -- | Sometimes a weaker equality relation than equalQName is -- appropriate, e.g no case significance in names, ... a name -- normalization function can be applied to the strings before comparing. -- Called by equalQName and equivQName equalQNameBy :: (String -> String -> Bool) -> QName -> QName -> Bool namePrefix :: QName -> String localPart :: QName -> String namespaceUri :: QName -> String newXName :: String -> XName nullXName :: XName isNullXName :: XName -> Bool newQName :: XName -> XName -> XName -> QName -- | Deprecated: use newQName instead with lp px ns param seq mkQName' :: XName -> XName -> XName -> QName namePrefix' :: QName -> XName localPart' :: QName -> XName namespaceUri' :: QName -> XName -- | set name prefix setNamePrefix' :: XName -> QName -> QName -- | set local part setLocalPart' :: XName -> QName -> QName -- | set name prefix setNamespaceUri' :: XName -> QName -> QName -- | builds the full name "prefix:localPart", if prefix is not null, else -- the local part is the result qualifiedName :: QName -> String -- | functional list version of qualifiedName used in xshow qualifiedName' :: QName -> String -> String -- | builds the "universal" name, that is the namespace uri surrounded with -- "{" and "}" followed by the local part (specialisation of -- buildUniversalName) universalName :: QName -> String -- | builds an "universal" uri, that is the namespace uri followed by the -- local part. This is usefull for RDF applications, where the subject, -- predicate and object often are concatenated from namespace uri and -- local part (specialisation of buildUniversalName) universalUri :: QName -> String -- | builds a string from the namespace uri and the local part. If the -- namespace uri is empty, the local part is returned, else namespace uri -- and local part are combined with the combining function given by the -- first parameter buildUniversalName :: (String -> String -> String) -> QName -> String -- | Normalization of URIs: Normalization is done by conversion into -- lowercase letters. A trailing "/" is ignored normalizeNsUri :: String -> String -- | Compute the name prefix and the namespace uri for a qualified name. -- -- This function does not test whether the name is a wellformed qualified -- name. see Namespaces in XML Rule [6] to [8]. Error checking is done -- with separate functions, see isWellformedQName and -- isWellformedQualifiedName for error checking. setNamespace :: NsEnv -> QName -> QName -- | test for wellformed NCName, rule [4] XML Namespaces isNCName :: String -> Bool -- | test for wellformed QName, rule [6] XML Namespaces predicate is used -- in filter valdateNamespaces. isWellformedQualifiedName :: String -> Bool -- | test for wellformed QName values. A QName is wellformed, if the local -- part is a NCName, the namePrefix, if not empty, is also a NCName. -- predicate is used in filter valdateNamespaces. isWellformedQName :: QName -> Bool -- | test whether an attribute name is a namesapce declaration name. If -- this is not the case True is the result, else the name must be a well -- formed namespace name: All namespace prefixes starting with "xml" are -- reserved for XML related definitions. predicate is used in filter -- valdateNamespaces. isWellformedNSDecl :: QName -> Bool -- | test for a namespace name to be well formed isWellformedNameSpaceName :: QName -> Bool -- | test whether a name is a namespace declaration attribute name isNameSpaceName :: QName -> Bool -- | predicate is used in filter valdateNamespaces. isDeclaredNamespace :: QName -> Bool xmlNamespaceXName :: XName xmlXName :: XName xmlnsNamespaceXName :: XName xmlnsXName :: XName xmlnsQN :: QName toNsEnv :: AssocList String String -> NsEnv instance GHC.Classes.Eq Text.XML.HXT.DOM.QualifiedName.XName instance GHC.Classes.Ord Text.XML.HXT.DOM.QualifiedName.XName instance Control.DeepSeq.NFData Text.XML.HXT.DOM.QualifiedName.XName instance Control.FlatSeq.WNFData Text.XML.HXT.DOM.QualifiedName.XName instance Data.Binary.Class.Binary Text.XML.HXT.DOM.QualifiedName.XName instance GHC.Classes.Eq Text.XML.HXT.DOM.QualifiedName.QName instance GHC.Classes.Ord Text.XML.HXT.DOM.QualifiedName.QName instance Control.DeepSeq.NFData Text.XML.HXT.DOM.QualifiedName.QName instance Control.FlatSeq.WNFData Text.XML.HXT.DOM.QualifiedName.QName instance GHC.Show.Show Text.XML.HXT.DOM.QualifiedName.QName instance Data.Binary.Class.Binary Text.XML.HXT.DOM.QualifiedName.QName -- | The core data types of the HXT DOM. module Text.XML.HXT.DOM.TypeDefs -- | Rose tree with XML nodes (XNode) type XmlTree = NTree XNode -- | List of rose trees with XML nodes type XmlTrees = NTrees XNode -- | Navigatable rose tree with XML nodes type XmlNavTree = NTZipper XNode -- | List of navigatable rose trees with XML nodes type XmlNavTrees = [NTZipper XNode] -- | Represents elements data XNode -- | ordinary text (leaf) XText :: String -> XNode -- | text represented more space efficient as bytestring (leaf) XBlob :: Blob -> XNode -- | character reference (leaf) XCharRef :: Int -> XNode -- | entity reference (leaf) XEntityRef :: String -> XNode -- | comment (leaf) XCmt :: String -> XNode -- | CDATA section (leaf) XCdata :: String -> XNode -- | Processing Instr with qualified name (leaf) with list of attributes. -- If tag name is xml, attributes are "version", "encoding", -- "standalone", else attribute list is empty, content is a text child -- node XPi :: QName -> XmlTrees -> XNode -- | tag with qualified name and list of attributes (inner node or leaf) XTag :: QName -> XmlTrees -> XNode -- | DTD element with assoc list for dtd element features XDTD :: DTDElem -> Attributes -> XNode -- | attribute with qualified name, the attribute value is stored in -- children XAttr :: QName -> XNode -- | error message with level and text XError :: Int -> String -> XNode -- | Evaluate an assoc list of strings rwnfAttributes :: Attributes -> () -- | Represents a DTD element data DTDElem -- | attr: name, system, public, XDTD elems as children DOCTYPE :: DTDElem -- | attr: name, kind -- -- name: element name -- -- kind: "EMPTY" | "ANY" | "#PCDATA" | children | mixed ELEMENT :: DTDElem -- | element content -- -- attr: kind, modifier -- -- modifier: "" | "?" | "*" | "+" -- -- kind: seq | choice CONTENT :: DTDElem -- | attributes: name - name of element -- -- value - name of attribute -- -- type: "CDATA" | "ID" | "IDREF" | "IDREFS" | "ENTITY" | "ENTITIES" | -- -- "NMTOKEN" | "NMTOKENS" |"NOTATION" | "ENUMTYPE" -- -- kind: "IMPLIED" | "DEFAULT" ATTLIST :: DTDElem -- | for entity declarations ENTITY :: DTDElem -- | for parameter entity declarations PENTITY :: DTDElem -- | for notations NOTATION :: DTDElem -- | for INCLUDEs, IGNOREs and peRefs: attr: type -- -- type = INCLUDE, IGNORE or %...; CONDSECT :: DTDElem -- | attr: name -- -- for lists of names in notation types or nmtokens in enumeration types NAME :: DTDElem -- | for Parameter Entity References in DTDs PEREF :: DTDElem -- | Binary large object implemented as a lazy bytestring type Blob = ByteString blobToString :: Blob -> String stringToBlob :: String -> Blob -- | Attribute list -- -- used for storing option lists and features of DTD parts type Attributes = AssocList String String -- | no error, everything is ok c_ok :: Int -- | Error level for XError, type warning c_warn :: Int -- | Error level for XError, type error c_err :: Int -- | Error level for XError, type fatal error c_fatal :: Int -- | data type for representing a set of nodes as a tree structure -- -- this structure is e.g. used to repesent the result of an XPath query -- such that the selected nodes can be processed or selected later in -- processing a document tree data XmlNodeSet XNS :: Bool -> [QName] -> ChildNodes -> XmlNodeSet -- | is this node part of the set ? [thisNode] :: XmlNodeSet -> Bool -- | the set of attribute nodes [attrNodes] :: XmlNodeSet -> [QName] -- | the set of child nodes, a list of pairs of index and node set [childNodes] :: XmlNodeSet -> ChildNodes type ChildNodes = [(Int, XmlNodeSet)] instance GHC.Show.Show Text.XML.HXT.DOM.TypeDefs.XmlNodeSet instance GHC.Classes.Eq Text.XML.HXT.DOM.TypeDefs.XmlNodeSet instance GHC.Show.Show Text.XML.HXT.DOM.TypeDefs.XNode instance GHC.Classes.Eq Text.XML.HXT.DOM.TypeDefs.XNode instance GHC.Read.Read Text.XML.HXT.DOM.TypeDefs.DTDElem instance GHC.Show.Show Text.XML.HXT.DOM.TypeDefs.DTDElem instance GHC.Enum.Enum Text.XML.HXT.DOM.TypeDefs.DTDElem instance GHC.Classes.Ord Text.XML.HXT.DOM.TypeDefs.DTDElem instance GHC.Classes.Eq Text.XML.HXT.DOM.TypeDefs.DTDElem instance Control.DeepSeq.NFData Text.XML.HXT.DOM.TypeDefs.XNode instance Control.FlatSeq.WNFData Text.XML.HXT.DOM.TypeDefs.XNode instance Data.Binary.Class.Binary Text.XML.HXT.DOM.TypeDefs.XNode instance Control.DeepSeq.NFData Text.XML.HXT.DOM.TypeDefs.DTDElem instance Control.FlatSeq.WNFData Text.XML.HXT.DOM.TypeDefs.DTDElem instance Data.Binary.Class.Binary Text.XML.HXT.DOM.TypeDefs.DTDElem -- | Version : $Id$ -- -- Datatypes and functions for building a content model for XML picklers. -- A schema is part of every pickler and can be used to derive a -- corrensponding DTD (or Relax NG schema). This schema further enables -- checking the picklers. module Text.XML.HXT.Arrow.Pickle.Schema -- | The datatype for modelling the structure of an data Schema Any :: Schema Seq :: [Schema] -> Schema [sc_l] :: Schema -> [Schema] Alt :: [Schema] -> Schema [sc_l] :: Schema -> [Schema] Rep :: Int -> Int -> Schema -> Schema [sc_lb] :: Schema -> Int [sc_ub] :: Schema -> Int [sc_1] :: Schema -> Schema Element :: Name -> Schema -> Schema [sc_n] :: Schema -> Name [sc_1] :: Schema -> Schema Attribute :: Name -> Schema -> Schema [sc_n] :: Schema -> Name [sc_1] :: Schema -> Schema ElemRef :: Name -> Schema [sc_n] :: Schema -> Name CharData :: DataTypeDescr -> Schema [sc_dt] :: Schema -> DataTypeDescr type Name = String type Schemas = [Schema] data DataTypeDescr DTDescr :: String -> String -> Attributes -> DataTypeDescr [dtLib] :: DataTypeDescr -> String [dtName] :: DataTypeDescr -> String [dtParams] :: DataTypeDescr -> Attributes -- | test: is schema a simple XML Schema datatype isScXsd :: (String -> Bool) -> Schema -> Bool -- | test: is type a fixed value attribute type isScFixed :: Schema -> Bool isScEnum :: Schema -> Bool isScElem :: Schema -> Bool isScAttr :: Schema -> Bool isScElemRef :: Schema -> Bool isScCharData :: Schema -> Bool isScSARE :: Schema -> Bool isScList :: Schema -> Bool isScOpt :: Schema -> Bool -- | access an attribute of a descr of an atomic type xsdParam :: String -> Schema -> String scDT :: String -> String -> Attributes -> Schema scDTxsd :: String -> Attributes -> Schema scString :: Schema scString1 :: Schema scFixed :: String -> Schema scEnum :: [String] -> Schema scNmtoken :: Schema scNmtokens :: Schema scEmpty :: Schema scSeq :: Schema -> Schema -> Schema scSeqs :: [Schema] -> Schema scNull :: Schema scAlt :: Schema -> Schema -> Schema scAlts :: [Schema] -> Schema scOption :: Schema -> Schema scList :: Schema -> Schema scList1 :: Schema -> Schema scOpt :: Schema -> Schema scRep :: Int -> Int -> Schema -> Schema scElem :: String -> Schema -> Schema scAttr :: String -> Schema -> Schema instance GHC.Show.Show Text.XML.HXT.Arrow.Pickle.Schema.Schema instance GHC.Classes.Eq Text.XML.HXT.Arrow.Pickle.Schema.Schema instance GHC.Show.Show Text.XML.HXT.Arrow.Pickle.Schema.DataTypeDescr instance GHC.Classes.Eq Text.XML.HXT.Arrow.Pickle.Schema.DataTypeDescr -- | The interface to the primitive DOM data types and constants and -- utility functions module Text.XML.HXT.DOM.Interface -- | Interface for XmlArrow to basic data types NTree and XmlTree -- -- If this module must be used in code working with arrows, it should be -- imported qualified e.g. as XN, to prevent name clashes. -- -- For code working on the "node and tree level" this module is the -- interface for writing code without using the constructor functions of -- XNode and NTree directly module Text.XML.HXT.DOM.XmlNode class XmlNode a where getName n = getElemName n `mplus` getAttrName n `mplus` getPiName n getQualifiedName n = getName n >>= return . qualifiedName getUniversalName n = getName n >>= return . universalName getUniversalUri n = getName n >>= return . universalUri getLocalPart n = getName n >>= return . localPart getNamePrefix n = getName n >>= return . namePrefix getNamespaceUri n = getName n >>= return . namespaceUri setText = changeText . const setBlob = changeBlob . const setCmt = changeCmt . const setName = changeName . const setElemName = changeElemName . const setElemAttrl = changeAttrl . const setAttrName = changeAttrName . const setPiName = changePiName . const setDTDAttrl = changeDTDAttrl . const isText :: XmlNode a => a -> Bool isBlob :: XmlNode a => a -> Bool isCharRef :: XmlNode a => a -> Bool isEntityRef :: XmlNode a => a -> Bool isCmt :: XmlNode a => a -> Bool isCdata :: XmlNode a => a -> Bool isPi :: XmlNode a => a -> Bool isElem :: XmlNode a => a -> Bool isRoot :: XmlNode a => a -> Bool isDTD :: XmlNode a => a -> Bool isAttr :: XmlNode a => a -> Bool isError :: XmlNode a => a -> Bool mkText :: XmlNode a => String -> a mkBlob :: XmlNode a => Blob -> a mkCharRef :: XmlNode a => Int -> a mkEntityRef :: XmlNode a => String -> a mkCmt :: XmlNode a => String -> a mkCdata :: XmlNode a => String -> a mkPi :: XmlNode a => QName -> XmlTrees -> a mkError :: XmlNode a => Int -> String -> a getText :: XmlNode a => a -> Maybe String getBlob :: XmlNode a => a -> Maybe Blob getCharRef :: XmlNode a => a -> Maybe Int getEntityRef :: XmlNode a => a -> Maybe String getCmt :: XmlNode a => a -> Maybe String getCdata :: XmlNode a => a -> Maybe String getPiName :: XmlNode a => a -> Maybe QName getPiContent :: XmlNode a => a -> Maybe XmlTrees getElemName :: XmlNode a => a -> Maybe QName getAttrl :: XmlNode a => a -> Maybe XmlTrees getDTDPart :: XmlNode a => a -> Maybe DTDElem getDTDAttrl :: XmlNode a => a -> Maybe Attributes getAttrName :: XmlNode a => a -> Maybe QName getErrorLevel :: XmlNode a => a -> Maybe Int getErrorMsg :: XmlNode a => a -> Maybe String getName :: XmlNode a => a -> Maybe QName getQualifiedName :: XmlNode a => a -> Maybe String getUniversalName :: XmlNode a => a -> Maybe String getUniversalUri :: XmlNode a => a -> Maybe String getLocalPart :: XmlNode a => a -> Maybe String getNamePrefix :: XmlNode a => a -> Maybe String getNamespaceUri :: XmlNode a => a -> Maybe String changeText :: XmlNode a => (String -> String) -> a -> a changeBlob :: XmlNode a => (Blob -> Blob) -> a -> a changeCmt :: XmlNode a => (String -> String) -> a -> a changeName :: XmlNode a => (QName -> QName) -> a -> a changeElemName :: XmlNode a => (QName -> QName) -> a -> a changeAttrl :: XmlNode a => (XmlTrees -> XmlTrees) -> a -> a changeAttrName :: XmlNode a => (QName -> QName) -> a -> a changePiName :: XmlNode a => (QName -> QName) -> a -> a changeDTDAttrl :: XmlNode a => (Attributes -> Attributes) -> a -> a setText :: XmlNode a => String -> a -> a setBlob :: XmlNode a => Blob -> a -> a setCmt :: XmlNode a => String -> a -> a setName :: XmlNode a => QName -> a -> a setElemName :: XmlNode a => QName -> a -> a setElemAttrl :: XmlNode a => XmlTrees -> a -> a setAttrName :: XmlNode a => QName -> a -> a setPiName :: XmlNode a => QName -> a -> a setDTDAttrl :: XmlNode a => Attributes -> a -> a mkElementNode :: QName -> XmlTrees -> XNode mkAttrNode :: QName -> XNode mkDTDNode :: DTDElem -> Attributes -> XNode mkElement :: QName -> XmlTrees -> XmlTrees -> XmlTree mkRoot :: XmlTrees -> XmlTrees -> XmlTree mkAttr :: QName -> XmlTrees -> XmlTree mkDTDElem :: DTDElem -> Attributes -> XmlTrees -> XmlTree addAttr :: XmlTree -> XmlTrees -> XmlTrees mergeAttrl :: XmlTrees -> XmlTrees -> XmlTrees -- | weak normalform versions of constructors mkElement' :: QName -> XmlTrees -> XmlTrees -> XmlTree mkRoot' :: XmlTrees -> XmlTrees -> XmlTree mkAttr' :: QName -> XmlTrees -> XmlTree mkText' :: String -> XmlTree mkCharRef' :: Int -> XmlTree mkEntityRef' :: String -> XmlTree mkCmt' :: String -> XmlTree mkCdata' :: String -> XmlTree mkPi' :: QName -> XmlTrees -> XmlTree mkError' :: Int -> String -> XmlTree mkDTDElem' :: DTDElem -> Attributes -> XmlTrees -> XmlTree toText :: XmlTree -> XmlTree concText :: XmlTree -> XmlTree -> XmlTrees mergeText :: XmlTree -> XmlTree -> XmlTrees instance Text.XML.HXT.DOM.XmlNode.XmlNode Text.XML.HXT.DOM.TypeDefs.XNode instance (Text.XML.HXT.DOM.XmlNode.XmlNode a, Data.Tree.Class.Tree t) => Text.XML.HXT.DOM.XmlNode.XmlNode (t a) -- | Version : $Id$ -- -- Functions for converting a pickler schema into a DTD module Text.XML.HXT.Arrow.Pickle.DTD data DTDdescr DTDdescr :: Name -> Schemas -> [(Name, Schemas)] -> DTDdescr -- | convert a DTD descr into XmlTrees dtdDescrToXml :: DTDdescr -> XmlTrees checkAttrModell :: Name -> Schemas -> XmlTrees checkAM :: Name -> Schema -> XmlTrees checkAMC :: Name -> Name -> Schema -> XmlTrees checkContentModell :: Name -> Schema -> XmlTrees scContToXml :: Schema -> (Attributes, XmlTrees) scWrap :: Schema -> Schema scCont :: Attributes -> Schema -> XmlTrees scConts :: Attributes -> Schemas -> XmlTrees scAttrToXml :: Schema -> (Attributes, XmlTrees) checkErr :: Bool -> String -> XmlTrees foundErr :: String -> XmlTrees -- | convert a pickler schema into a DTD descr dtdDescr :: Schema -> DTDdescr elementDeclarations :: Schema -> Schemas elementDecs :: Schemas -> Schemas -> Schemas elemNames :: Schemas -> [Name] elemName :: Schema -> Maybe Name elemRefs :: Schemas -> Schemas attrDec :: Schema -> [(Name, Schemas)] remAttrDec :: Schema -> Schema instance GHC.Show.Show Text.XML.HXT.Arrow.Pickle.DTD.DTDdescr -- | XML tree conversion to external string representation module Text.XML.HXT.DOM.ShowXml -- | convert a list of trees into a string -- -- see also : xmlTreesToText for filter version, xread -- for the inverse operation xshow :: XmlTrees -> String -- | convert an XML tree into a binary large object (a bytestring) xshowBlob :: XmlTrees -> Blob -- | convert a list of trees into a blob. -- -- Apply a quoting function for XML quoting of content, a 2. quoting -- funtion for attribute values and an encoding function after tree -- conversion xshow' :: (Char -> StringFct) -> (Char -> StringFct) -> (Char -> StringFct) -> XmlTrees -> Blob xshow'' :: (Char -> StringFct) -> (Char -> StringFct) -> XmlTrees -> String -- | Format a xml tree in tree representation module Text.XML.HXT.DOM.FormatXmlTree formatXmlTree :: XmlTree -> String formatXmlContents :: XmlTree -> XmlTrees -- | Parsec parser for XML tokens module Text.XML.HXT.Parser.XmlTokenParser allBut :: (XParser s Char -> XParser s String) -> String -> XParser s String allBut1 :: (XParser s Char -> XParser s String) -> (Char -> Bool) -> String -> XParser s String amp :: XParser s () asciiLetter :: XParser s Char attrChar :: String -> XParser s String attrValue :: XParser s String bar :: XParser s () charRef :: XParser s Int checkString :: String -> XParser s () comma :: XParser s () dq :: XParser s () encName :: XParser s String entityRef :: XParser s String entityValue :: XParser s String eq :: XParser s () gt :: XParser s () keyword :: String -> XParser s String keywords :: [String] -> XParser s String lpar :: XParser s () lt :: XParser s () name :: XParser s String names :: XParser s [String] ncName :: XParser s String nmtoken :: XParser s String nmtokens :: XParser s [String] peReference :: XParser s String pubidLiteral :: XParser s String qName :: XParser s (String, String) quoted :: XParser s a -> XParser s a reference :: XParser s String rpar :: XParser s () semi :: XParser s () separator :: Char -> XParser s () singleChar :: String -> XParser s Char singleChars :: String -> XParser s String skipS :: XParser s () skipS0 :: XParser s () sPace :: XParser s String sPace0 :: XParser s String sq :: XParser s () systemLiteral :: XParser s String versionNum :: XParser s String concRes :: XParser s [[a]] -> XParser s [a] mkList :: XParser s a -> XParser s [a] nameT :: XParser s XmlTree nmtokenT :: XParser s XmlTree entityValueT :: XParser s XmlTrees entityTokensT :: String -> XParser s XmlTrees entityCharT :: String -> XParser s XmlTree attrValueT :: XParser s XmlTrees attrValueT' :: String -> XParser s XmlTrees referenceT :: XParser s XmlTree charRefT :: XParser s XmlTree entityRefT :: XParser s XmlTree peReferenceT :: XParser s XmlTree singleCharsT :: String -> XParser s XmlTree mergeTextNodes :: XmlTrees -> XmlTrees -- | Parsec parser for tokenizing DTD declarations for ELEMENT, ATTLIST, -- ENTITY and NOTATION module Text.XML.HXT.Parser.XmlDTDTokenParser dtdDeclTokenizer :: XParser s XmlTree dtdDeclStart :: XParser s (DTDElem, Attributes) dtdDeclEnd :: XParser s () dtdToken :: XParser s XmlTree peReference :: XParser s XmlTree entityValue :: XParser s XmlTree dtdChars :: XParser s XmlTree percent :: XParser s XmlTree -- | Parsec parser for DTD declarations for ELEMENT, ATTLIST, ENTITY and -- NOTATION declarations module Text.XML.HXT.Parser.XmlDTDParser -- | parse a tokenized DTD declaration represented by a DTD tree. The -- content is represented by the children containing text and parameter -- entity reference nodes. The parameter entity reference nodes contain -- their value in the children list, consisting of text and possibly -- again parameter entity reference nodes. This structure is build by the -- parameter entity substitution. Output is again a DTD declaration node, -- but this time completely parsed and ready for further DTD processing parseXmlDTDdecl :: XmlTree -> XmlTrees parseXmlDTDdeclPart :: XmlTree -> XmlTrees parseXmlDTDEntityValue :: XmlTree -> XmlTrees elementDecl :: SParser XmlTrees attlistDecl :: SParser XmlTrees entityDecl :: SParser XmlTrees notationDecl :: SParser XmlTrees -- | Xml Parsec parser with pure filter interface module Text.XML.HXT.Parser.XmlParsec charData :: XParser s XmlTrees charData' :: XParser s XmlTree comment :: XParser s XmlTree pI :: XParser s XmlTree cDSect :: XParser s XmlTree document :: XParser s XmlTree document' :: XParser s XmlTrees prolog :: XParser s XmlTrees xMLDecl :: XParser s XmlTrees xMLDecl' :: XParser s XmlTrees versionInfo :: XParser s XmlTrees misc :: XParser s XmlTree doctypedecl :: XParser s XmlTrees markupdecl :: XParser s XmlTrees sDDecl :: XParser s XmlTrees element :: XParser s XmlTree content :: XParser s XmlTrees contentWithTextDecl :: XParser s XmlTrees textDecl :: XParser s XmlTrees encodingDecl :: XParser s XmlTrees -- | the inverse function to xshow, (for XML content). -- -- the string parameter is parsed with the XML content parser. result is -- the list of trees or in case of an error a single element list with -- the error message as node. No entity or character subtitution is done -- here, but the XML parser can do this for the predefined XML or the -- char references for performance reasons -- -- see also: parseXmlContent xread :: String -> XmlTrees xreadDoc :: String -> XmlTrees -- | the filter version of xread parseXmlContent :: XmlTree -> XmlTrees parseXmlDocEncodingSpec :: XmlTree -> XmlTrees parseXmlDocument :: String -> String -> XmlTrees -- | Parser for parts of a DTD parseXmlDTDPart :: String -> XmlTree -> XmlTrees -- | try to parse a xml encoding spec. -- -- parseXmlEncodingSpec :: SimpleXParser XmlTree -> XmlTree -> XmlTrees parseXmlEntityEncodingSpec :: XmlTree -> XmlTrees -- | Parser for entity substitution within attribute values parseXmlEntityValueAsAttrValue :: String -> XmlTree -> XmlTrees -- | Parser for general entites parseXmlEntityValueAsContent :: String -> XmlTree -> XmlTrees -- | general parser for parsing arbitray parts of a XML document parseXmlPart :: SimpleXParser XmlTrees -> String -> String -> XmlTree -> XmlTrees -- | a more general version of parseXmlContent. The parser to be -- used and the context are extra parameter parseXmlText :: SimpleXParser XmlTrees -> XPState () -> String -> XmlTree -> XmlTrees -- | Parser for NMTOKENs parseNMToken :: String -> XmlTree -> XmlTrees -- | Parser for XML names parseName :: String -> XmlTree -> XmlTrees removeEncodingSpec :: XmlTree -> XmlTrees -- | This parser tries to interprete everything as HTML no errors are -- emitted during parsing. If something looks weired, warning messages -- are inserted in the document tree. -- -- All filter are pure XmlFilter, errror handling and IO is done in -- HtmlParser or other modules module Text.XML.HXT.Parser.HtmlParsec parseHtmlText :: String -> XmlTree -> XmlTrees parseHtmlDocument :: String -> String -> XmlTrees parseHtmlContent :: String -> XmlTrees isEmptyHtmlTag :: String -> Bool isInnerHtmlTagOf :: String -> String -> Bool closesHtmlTag :: String -> String -> Bool emptyHtmlTags :: [String] -- | Arrows for managing an explicit state -- -- State arrows work similar to state monads. A state value is threaded -- through the application of arrows. module Control.Arrow.ArrowState -- | The interface for accessing and changing the state component. -- -- Multi parameter classes and functional dependencies are required. class Arrow a => ArrowState s a | a -> s where getState = accessState (\ s _x -> s) setState = changeState (\ _s x -> x) nextState sf = changeState (\ s -> const (sf s)) >>> getState -- | change the state of a state arrow by applying a function for computing -- a new state from the old and the arrow input. Result is the arrow -- input changeState :: ArrowState s a => (s -> b -> s) -> a b b -- | access the state with a function using the arrow input as data for -- selecting state components. accessState :: ArrowState s a => (s -> b -> c) -> a b c -- | read the complete state, ignore arrow input -- -- definition: getState = accessState (\ s x -> s) getState :: ArrowState s a => a b s -- | overwrite the old state -- -- definition: setState = changeState (\ s x -> x) setState :: ArrowState s a => a s s -- | change state (and ignore input) and return new state -- -- convenience function, usefull for generating e.g. unique identifiers: -- -- example with SLA state list arrows -- --
--   newId :: SLA Int b String
--   newId = nextState (+1)
--           >>>
--           arr (('#':) . show)
--   
--   runSLA 0 (newId <+> newId <+> newId) undefined
--     = ["#1", "#2", "#3"]
--   
nextState :: ArrowState s a => (s -> s) -> a b s -- | The list arrow class -- -- This module defines the interface for list arrows. -- -- A list arrow is a function, that gives a list of results for a given -- argument. A single element result represents a normal function. An -- empty list oven indicates, the function is undefined for the given -- argument. The empty list may also represent False, none empty lists -- True. A list with more than one element gives all results for a -- nondeterministic function. module Control.Arrow.ArrowList -- | The interface for list arrows -- -- Only mkA, isA '(>>.)' don't have default -- implementations class (Arrow a, ArrowPlus a, ArrowZero a, ArrowApply a) => ArrowList a where arr2 = arr . uncurry arr3 f = arr (\ ~(x1, ~(x2, x3)) -> f x1 x2 x3) arr4 f = arr (\ ~(x1, ~(x2, ~(x3, x4))) -> f x1 x2 x3 x4) arr2A f = first (arr f) >>> app arr2L = arrL . uncurry constA = arr . const constL = arrL . const af >. f = af >>. ((: []) . f) listA af = af >>. (: []) unlistA = arrL id this = returnA none = zeroArrow withDefault a d = a >>. \ x -> if null x then [d] else x single f = f >>. take 1 applyA f = (f &&& this) >>> app g $< f = applyA (f >>> arr g) f $<< g = applyA (g >>> arr2 f) f $<<< g = applyA (g >>> arr3 f) f $<<<< g = applyA (g >>> arr4 f) g $<$ f = applyA (listA (f >>> arr g) >>> arr seqA) mergeA op = (\ x -> arr fst `op` constA (snd x)) $< this perform f = listA f &&& this >>> arr snd catA = foldl (<+>) none seqA = foldl (>>>) this -- | construction of a 2 argument arrow from a binary function | | example: -- a1 &&& a2 >>> arr2 f arr2 :: ArrowList a => (b1 -> b2 -> c) -> a (b1, b2) c -- | construction of a 3 argument arrow from a 3-ary function | | example: -- a1 &&& a2 &&& a3 >>> arr3 f -- arr3 :: ArrowList a => (b1 -> b2 -> b3 -> c) -> a (b1, (b2, b3)) c -- | construction of a 4 argument arrow from a 4-ary function | | example: -- a1 &&& a2 &&& a3 &&& a4 -- >>> arr4 f arr4 :: ArrowList a => (b1 -> b2 -> b3 -> b4 -> c) -> a (b1, (b2, (b3, b4))) c -- | construction of a 2 argument arrow from a singe argument arrow arr2A :: ArrowList a => (b -> a c d) -> a (b, c) d -- | constructor for a list arrow from a function with a list as result arrL :: ArrowList a => (b -> [c]) -> a b c -- | constructor for a list arrow with 2 arguments arr2L :: ArrowList a => (b -> c -> [d]) -> a (b, c) d -- | constructor for a const arrow: constA = arr . const constA :: ArrowList a => c -> a b c -- | constructor for a const arrow: constL = arrL . const constL :: ArrowList a => [c] -> a b c -- | builds an arrow from a predicate. If the predicate holds, the single -- list containing the input is returned, else the empty list isA :: ArrowList a => (b -> Bool) -> a b b -- | combinator for converting the result of a list arrow into another list -- -- example: foo >>. reverse reverses the the result of -- foo -- -- example: foo >>. take 1 constructs a deterministic -- version of foo by deleting all further results (>>.) :: ArrowList a => a b c -> ([c] -> [d]) -> a b d -- | combinator for converting the result of an arrow into a single element -- result (>.) :: ArrowList a => a b c -> ([c] -> d) -> a b d -- | combinator for converting an arrow into a determinstic version with -- all results collected in a single element list -- --
--   listA af = af >>. (:[])
--   
-- -- this is useful when the list of results computed by an arrow must be -- manipulated (e.g. sorted) -- -- example for sorting the results of a filter -- --
--   collectAndSort         :: a b c -> a b c
--   
--   collectAndSort collect = listA collect >>> arrL sort
--   
listA :: ArrowList a => a b c -> a b [c] -- | the inverse of listA -- --
--   listA af >>> unlistA = af
--   
-- -- unlistA is defined as arrL id unlistA :: ArrowList a => a [b] b -- | the identity arrow, alias for returnA this :: ArrowList a => a b b -- | the zero arrow, alias for zeroArrow none :: ArrowList a => a b c -- | converts an arrow, that may fail, into an arrow that always succeeds -- -- example: withDefault none "abc" is equivalent to -- constA "abc" withDefault :: ArrowList a => a b c -> c -> a b c -- | makes a list arrow deterministic, the number of results is at most 1 -- -- definition -- --
--   single f = f >>. take 1
--   
-- -- examples with strings: -- --
--   runLA ( single none ) "x" == []
--   runLA ( single this ) "x" == ["x"]
--   runLA ( single
--           (constA "y"
--            <+> this ) ) "x" == ["y"]
--   
single :: ArrowList a => a b c -> a b c -- | compute an arrow from the input and apply the arrow to this input -- -- definition: (f &&& this) >>> app -- -- in a point free style, there is no way to use an argument in 2 places, -- this is a combinator for simulating this. first the argument is used -- to compute an arrow, then this new arrow is applied to the input -- -- applyA coresponds to: apply f x = let g = f x in g x -- -- see also: $<, $<<, $<<<, -- $<<<<, $<$ applyA :: ArrowList a => a b (a b c) -> a b c -- | compute the parameter for an arrow with extra parameters from the -- input and apply the arrow for all parameter values to the input -- -- a kind of "function call" for arrows, useful for joining arrows -- --
--   infixl 2 ($<)
--   
-- -- definition: -- --
--   g $< f = applyA (f >>> arr g)
--   
-- -- if f fails, the whole arrow fails, e.g. g $< none == -- none -- -- if f computes n values and g is deterministic, the -- whole arrow computes n values -- -- examples with simple list arrows with strings -- --
--   prefixString   :: String -> a String String
--   prefixString s =  arr (s++)
--   
--   runLA ( prefixString $< none           ) "x" == []
--   runLA ( prefixString $< constA "y"     ) "x" == ["yx"]
--   runLA ( prefixString $< this           ) "x" == ["xx"]
--   runLA ( prefixString $< constA "y"
--                           <+> constA "z" ) "x" == ["yx","zx"]
--   runLA ( prefixString $< constA "y"
--                           <+> this
--                           <+> constA "z" ) "x" == ["yx","xx","zx"]
--   
-- -- see also: applyA, $<<, $<<<, -- $<<<<, $<$ ($<) :: ArrowList a => (c -> a b d) -> a b c -> a b d -- | binary version of $< -- -- example with simple list arrows with strings -- --
--   infixString    :: String -> String -> a String String
--   infixString s1 s2
--                  = arr (\ s -> s1 ++ s ++ s2)
--   
--   runLA ( infixString $<< constA "y" &&& constA "z" ) "x" = ["yxz"]
--   runLA ( infixString $<< this &&& this             ) "x" = ["xxx"]
--   runLA ( infixString $<< constA "y"
--                           &&& (constA "z" <+> this) ) "x" = ["yxz", "yxx"]
--   
($<<) :: ArrowList a => (c1 -> c2 -> a b d) -> a b (c1, c2) -> a b d -- | version of $< for arrows with 3 extra parameters -- -- typical usage -- --
--   f $<<< g1 &&& g2 &&& g3
--   
($<<<) :: ArrowList a => (c1 -> c2 -> c3 -> a b d) -> a b (c1, (c2, c3)) -> a b d -- | version of $< for arrows with 4 extra parameters -- -- typical usage -- --
--   f $<<<< g1 &&& g2 &&& g3 &&& g4
--   
($<<<<) :: ArrowList a => (c1 -> c2 -> c3 -> c4 -> a b d) -> a b (c1, (c2, (c3, c4))) -> a b d -- | compute the parameter for an arrow f with an extra parameter -- by an arrow g and apply all the results from g -- sequentially to the input -- --
--   infixl 2 ($<$)
--   
-- -- typical usage: -- --
--   g :: a b c
--   g = ...
--   
--   f :: c -> a b b
--   f x = ... x ...
--   
--   f $<$ g
--   
-- -- f computes the extra parameters for g from the input -- of type b and g is applied with this parameter to -- the input. This allows programming in a point wise style in -- g, which becomes neccessary, when a value is needed more than -- once. -- -- this combinator is useful, when transforming a single value (document) -- step by step, with g for collecting the data for all steps, -- and f for transforming the input step by step -- -- if g is deterministic (computes exactly one result), g -- $<$ f == g $< f holds -- -- if g fails, f $<$ g == this -- -- if g computes more than one result, f is applied -- sequentially to the input for every result from g -- -- examples with simple list arrows with strings -- --
--   prefixString   :: String -> a String String
--   prefixString s =  arr (s++)
--   
--   runLA ( prefixString $<$ none                      ) "x" == ["x"]
--   runLA ( prefixString $<$ constA "y"                ) "x" == ["yx"]
--   runLA ( prefixString $<$ constA "y" <+> constA "z" ) "x" == ["zyx"]
--   runLA ( prefixString $<$ constA "y" <+> this
--                            <+> constA "z"            ) "x" == ["zxyx"]
--   
-- -- example with two extra parameter -- --
--   g1 :: a b c1
--   g2 :: a b c2
--   
--   f          :: (c1, c2) -> a b b
--   f (x1, x2) =  ... x1 ... x2 ...
--   
--   f $<$ g1 &&& g2
--   
-- -- see also: applyA, $< ($<$) :: ArrowList a => (c -> (a b b)) -> a b c -> a b b -- | merge the result pairs of an arrow with type a a1 (b1, b2) by -- combining the tuple components with the op arrow -- -- examples with simple list arrows working on strings and XmlTrees -- --
--   a1 :: a String (XmlTree, XmlTree)
--   a1 = selem "foo" [this >>> mkText]
--        &&&
--        selem "bar" [arr (++"0") >>> mkText]
--   
--   runLA (a1 >>> mergeA (<+>) >>> xshow this) "42" == ["<foo>42</foo>","<bar>420</bar>"]
--   runLA (a1 >>> mergeA (+=)  >>> xshow this) "42" == ["<foo>42<bar>420</bar></foo>"]
--   
-- -- see also: applyA, $< and += in class -- ArrowXml mergeA :: ArrowList a => (a (a1, b1) a1 -> a (a1, b1) b1 -> a (a1, b1) c) -> a (a1, b1) c -- | useful only for arrows with side effects: perform applies an arrow to -- the input ignores the result and returns the input -- -- example: ... >>> perform someTraceArrow >>> ... -- perform :: ArrowList a => a b c -> a b b -- | generalization of arrow combinator <+> -- -- definition: catA = foldl (<+>) none catA :: ArrowList a => [a b c] -> a b c -- | generalization of arrow combinator >>> -- -- definition: seqA = foldl (>>>) this seqA :: ArrowList a => [a b b] -> a b b -- | Arrows for evaluation of normal form results module Control.Arrow.ArrowNF -- | complete evaluation of an arrow result using DeepSeq -- -- this is sometimes useful for preventing space leaks, especially after -- reading and validation of a document, all DTD stuff is not longer in -- use and can be recycled by the GC. strictA :: (Arrow a, NFData b) => a b b class (Arrow a) => ArrowNF a where rnfA f = f >>^ (\ x -> deepseq x x) rnfA :: (ArrowNF a, NFData c) => a b c -> a b c -- | partial evaluation of an arrow result using FlatSeq -- -- There are tow arrows with force the partial evaluation. By convention -- the 2. should be less lazy than the 1. -- -- These arrows are sometimes useful for preventing space leaks, -- especially when parsing complex data structures. In many cases the -- evaluated AST is more space efficient than the unevaluaded with a lot -- of closures. class (Arrow a, ArrowList a) => ArrowWNF a where rwnfA f = f >>. \ x -> rlnf rwnf x `seq` x rwnf2A f = f >>. \ x -> rlnf rwnf2 x `seq` x rwnfA :: (ArrowWNF a, WNFData c) => a b c -> a b c rwnf2A :: (ArrowWNF a, WNFData c) => a b c -> a b c -- | Conditionals for List Arrows -- -- This module defines conditional combinators for list arrows. -- -- The empty list as result represents False, none empty lists True. module Control.Arrow.ArrowIf -- | The interface for arrows as conditionals. -- -- Requires list arrows because False is represented as empty list, True -- as none empty lists. -- -- Only ifA and orElse don't have default implementations class ArrowList a => ArrowIf a where ifP p = ifA (isA p) neg f = ifA f none this f `when` g = ifA g f this f `whenP` g = ifP g f this f `whenNot` g = ifA g this f f `whenNotP` g = ifP g this f f `guards` g = ifA f g none f `guardsP` g = ifP f g none filterA f = ifA f this none f `containing` g = f >>> g `guards` this f `notContaining` g = f >>> ifA g none this choiceA = foldr ifA' none where ifA' (g :-> f) = ifA g f tagA p = ifA p (arr Left) (arr Right) spanA p = ifA (arrL (take 1) >>> p) (arr head &&& (arr tail >>> spanA p) >>> arr (\ ~(x, ~(xs, ys)) -> (x : xs, ys))) (arr (\ l -> ([], l))) partitionA p = listA (arrL id >>> tagA p) >>^ ((\ ~(l1, l2) -> (unTag l1, unTag l2)) . partition (isLeft)) where isLeft (Left _) = True isLeft _ = False unTag = map (either id id) -- | if lifted to arrows ifA :: ArrowIf a => a b c -> a b d -> a b d -> a b d -- | shortcut: ifP p = ifA (isA p) ifP :: ArrowIf a => (b -> Bool) -> a b d -> a b d -> a b d -- | negation: neg f = ifA f none this neg :: ArrowIf a => a b c -> a b b -- | f `when` g : when the predicate g holds, f is applied, else -- the identity filter this when :: ArrowIf a => a b b -> a b c -> a b b -- | shortcut: f `whenP` p = f `when` (isA p) whenP :: ArrowIf a => a b b -> (b -> Bool) -> a b b -- | f `whenNot` g : when the predicate g does not hold, f is -- applied, else the identity filter this whenNot :: ArrowIf a => a b b -> a b c -> a b b -- | like whenP whenNotP :: ArrowIf a => a b b -> (b -> Bool) -> a b b -- | g `guards` f : when the predicate g holds, f is applied, -- else none guards :: ArrowIf a => a b c -> a b d -> a b d -- | like whenP guardsP :: ArrowIf a => (b -> Bool) -> a b d -> a b d -- | shortcut for f guards this filterA :: ArrowIf a => a b c -> a b b -- | f `containing` g : keep only those results from f for which -- g holds -- -- definition: f `containing` g = f >>> g `guards` this -- containing :: ArrowIf a => a b c -> a c d -> a b c -- | f `notContaining` g : keep only those results from f for -- which g does not hold -- -- definition: f `notContaining` g = f >>> ifA g none this -- notContaining :: ArrowIf a => a b c -> a c d -> a b c -- | f `orElse` g : directional choice: if f succeeds, the -- result of f is the result, else g is applied orElse :: ArrowIf a => a b c -> a b c -> a b c -- | generalisation of orElse for multi way branches like in case -- expressions. -- -- An auxiliary data type IfThen with an infix constructor -- :-> is used for writing multi way branches -- -- example: choiceA [ p1 :-> e1, p2 :-> e2, this :-> -- default ] choiceA :: ArrowIf a => [IfThen (a b c) (a b d)] -> a b d -- | tag a value with Left or Right, if arrow has success, input is tagged -- with Left, else with Right tagA :: ArrowIf a => a b c -> a b (Either b b) -- | split a list value with an arrow and returns a pair of lists. This is -- the arrow version of span. The arrow is deterministic. -- -- example: runLA (spanA (isA (/= '-'))) "abc-def" gives -- [("abc","-def")] as result spanA :: ArrowIf a => a b b -> a [b] ([b], [b]) -- | partition a list of values into a pair of lists -- -- This is the arrow Version of partition partitionA :: ArrowIf a => a b b -> a [b] ([b], [b]) -- | an auxiliary data type for choiceA data IfThen a b (:->) :: a -> b -> IfThen a b -- | List arrows for navigatable trees -- -- Trees that implement the Data.Tree.NavigatableTree.Class -- interface, can be processed with these arrows. module Control.Arrow.ArrowNavigatableTree -- | The interface for navigatable tree arrows -- -- all functions have default implementations class (ArrowList a) => ArrowNavigatableTree a where moveUp = arrL $ maybeToList . mvUp moveDown = arrL $ maybeToList . mvDown moveLeft = arrL $ maybeToList . mvLeft moveRight = arrL $ maybeToList . mvRight moveUp :: (ArrowNavigatableTree a, NavigatableTree t) => a (t b) (t b) moveDown :: (ArrowNavigatableTree a, NavigatableTree t) => a (t b) (t b) moveLeft :: (ArrowNavigatableTree a, NavigatableTree t) => a (t b) (t b) moveRight :: (ArrowNavigatableTree a, NavigatableTree t) => a (t b) (t b) parentAxis :: (ArrowList a, NavigatableTree t) => a (t b) (t b) -- | XPath axis: ancestor ancestorAxis :: (ArrowList a, NavigatableTree t) => a (t b) (t b) -- | XPath axis: ancestor or self ancestorOrSelfAxis :: (ArrowList a, NavigatableTree t) => a (t b) (t b) -- | XPath axis: child childAxis :: (ArrowList a, NavigatableTree t) => a (t b) (t b) -- | XPath axis: descendant descendantAxis :: (ArrowList a, NavigatableTree t) => a (t b) (t b) -- | XPath axis: descendant or self descendantOrSelfAxis :: (ArrowList a, NavigatableTree t) => a (t b) (t b) -- | not an XPath axis but useful: descendant or following descendantOrFollowingAxis :: (ArrowList a, NavigatableTree t) => a (t b) (t b) -- | not an official XPath axis but useful: reverse descendant or self, -- used in preceding axis revDescendantOrSelfAxis :: (ArrowList a, NavigatableTree t) => a (t b) (t b) -- | XPath axis: following sibling followingSiblingAxis :: (ArrowList a, NavigatableTree t) => a (t b) (t b) -- | XPath axis: preceeding sibling precedingSiblingAxis :: (ArrowList a, NavigatableTree t) => a (t b) (t b) -- | XPath axis: self selfAxis :: (ArrowList a, NavigatableTree t) => a (t b) (t b) -- | XPath axis: following followingAxis :: (ArrowList a, NavigatableTree t) => a (t b) (t b) -- | XPath axis: preceding precedingAxis :: (ArrowList a, NavigatableTree t) => a (t b) (t b) -- | move to the root moveToRoot :: (Arrow a, NavigatableTree t) => a (t b) (t b) isAtRoot :: (ArrowList a, NavigatableTree t) => a (t b) (t b) -- | Conversion from a tree into a navigatable tree addNav :: (ArrowList a, NavigatableTreeToTree nt t) => a (t b) (nt b) -- | Conversion from a navigatable tree into an ordinary tree remNav :: (ArrowList a, NavigatableTreeToTree nt t) => a (nt b) (t b) -- | apply an operation using navigation to an ordinary tree -- -- This root and all children may be visited in arbitrary order withNav :: (ArrowList a, NavigatableTreeToTree nt t) => a (nt b) (nt c) -> a (t b) (t c) -- | apply a simple operation without use of navigation to a navigatable -- tree -- -- This enables to apply arbitrary tree operations to navigatable trees withoutNav :: (ArrowList a, NavigatableTreeToTree nt t, NavigatableTreeModify nt t) => a (t b) (t b) -> a (nt b) (nt b) -- | Filter an axis with an ordinary tree predicate -- -- Example: In a tree of Ints find all nodes in the subtrees (in -- preorder) that have label 42 -- --
--   descendantAxis >>> filterAxis (hasNode (== 42))
--   
-- -- Example: In an XML Tree find the following nodes of a node with -- attribute id and value 42 -- --
--   descendantAxis >>> filterAxis (hasAttrValue "id" (=="42")) >>> followingAxis
--   
filterAxis :: (ArrowIf a, NavigatableTreeToTree nt t) => a (t b) c -> a (nt b) (nt b) -- | Move to the next tree on a given axis. Deterministic arrow -- -- Example: Move to the next node in a preorder visit: next child or else -- next following -- --
--   moveOn descendantOrFollowingAxis
--   
moveOn :: (ArrowList a, NavigatableTree t) => a (t b) (t b) -> a (t b) (t b) -- | Change the current subtree of a navigatable tree. -- -- The arrow for computing the changes should be deterministic. If it -- fails nothing is changed. changeThisTree :: (ArrowList a, ArrowIf a, NavigatableTreeToTree nt t, NavigatableTreeModify nt t) => a (t b) (t b) -> a (nt b) (nt b) -- | Substitute the current subtree of a navigatable tree by a given tree substThisTree :: (ArrowList a, ArrowIf a, NavigatableTreeToTree nt t, NavigatableTreeModify nt t) => t b -> a (nt b) (nt b) -- | apply an ordinary arrow to the current subtree of a navigatabe tree -- and add the result trees in front of the current tree. -- -- If this arrow is applied to the root, it will fail, because we want a -- tree as result, not a forest. addToTheLeft :: (ArrowList a, NavigatableTreeToTree nt t, NavigatableTreeModify nt t) => a (t b) (t b) -> a (nt b) (nt b) -- | apply an ordinary arrow to the current subtree of a navigatabe tree -- and add the result trees behind the current tree. -- -- If this arrow is applied to the root, it will fail, because we want a -- tree as result, not a forest. addToTheRight :: (ArrowList a, NavigatableTreeToTree nt t, NavigatableTreeModify nt t) => a (t b) (t b) -> a (nt b) (nt b) -- | addToOneSide does the real work for addToTheLeft and -- addToTheRight addToOneSide :: (ArrowList a, NavigatableTreeToTree nt t, NavigatableTreeModify nt t) => (Maybe (nt b) -> [t b] -> Maybe (nt b)) -> a (t b) (t b) -> a (nt b) (nt b) -- | drop the direct left sibling tree of the given navigatable tree -- -- If this arrow is applied to the root or a leftmost tree, it will fail, -- because there is nothing to remove dropFromTheLeft :: (ArrowList a, NavigatableTreeModify nt t) => a (nt b) (nt b) -- | drop the direct left sibling tree of the given navigatable tree -- -- If this arrow is applied to the root or a rightmost tree, it will -- fail, because there is nothing to remove dropFromTheRight :: (ArrowList a, NavigatableTreeModify nt t) => a (nt b) (nt b) -- | List arrows for tree processing. -- -- Trees that implement the Data.Tree.Class interface, can be -- processed with these arrows. module Control.Arrow.ArrowTree -- | The interface for tree arrows -- -- all functions have default implementations class (ArrowPlus a, ArrowIf a) => ArrowTree a where mkLeaf = constA . mkLeaf mkTree n = constA . mkTree n getChildren = arrL getChildren getNode = arr getNode hasNode p = (getNode >>> isA p) `guards` this setChildren cs = arr (setChildren cs) setNode n = arr (setNode n) changeChildren csf = arr (changeChildren csf) changeNode nf = arr (changeNode nf) processChildren f = arr getNode &&& listA (arrL getChildren >>> f) >>> arr2 mkTree replaceChildren f = arr getNode &&& listA f >>> arr2 mkTree f /> g = f >>> getChildren >>> g f //> g = f >>> getChildren >>> deep g f >> g) deep f = f `orElse` (getChildren >>> deep f) deepest f = (getChildren >>> deepest f) `orElse` f multi f = f <+> (getChildren >>> multi f) processBottomUp f = processChildren (processBottomUp f) >>> f processTopDown f = f >>> processChildren (processTopDown f) processBottomUpWhenNot f p = (processChildren (processBottomUpWhenNot f p) >>> f) `whenNot` p processTopDownUntil f = f `orElse` processChildren (processTopDownUntil f) insertChildrenAt i f = listA f &&& this >>> arr2 insertAt where insertAt newcs = changeChildren (\ cs -> let (cs1, cs2) = splitAt i cs in cs1 ++ newcs ++ cs2) insertChildrenAfter p f = replaceChildren (((listA getChildren >>> spanA p) &&& listA f) >>> arr2L (\ (xs1, xs2) xs -> xs1 ++ xs ++ xs2)) insertTreeTemplate template choices = insertTree $< this where insertTree t = template >>> processTemplate where processTemplate = choiceA choices' `orElse` processChildren processTemplate choices' = map feedTree choices feedTree (cond :-> action) = cond :-> (constA t >>> action) -- | construct a leaf mkLeaf :: (ArrowTree a, Tree t) => b -> a c (t b) -- | construct an inner node mkTree :: (ArrowTree a, Tree t) => b -> [t b] -> a c (t b) -- | select the children of the root of a tree getChildren :: (ArrowTree a, Tree t) => a (t b) (t b) -- | select the node info of the root of a tree getNode :: (ArrowTree a, Tree t) => a (t b) b -- | select the attribute of the root of a tree hasNode :: (ArrowTree a, Tree t) => (b -> Bool) -> a (t b) (t b) -- | substitute the children of the root of a tree setChildren :: (ArrowTree a, Tree t) => [t b] -> a (t b) (t b) -- | substitute the attribute of the root of a tree setNode :: (ArrowTree a, Tree t) => b -> a (t b) (t b) -- | edit the children of the root of a tree changeChildren :: (ArrowTree a, Tree t) => ([t b] -> [t b]) -> a (t b) (t b) -- | edit the attribute of the root of a tree changeNode :: (ArrowTree a, Tree t) => (b -> b) -> a (t b) (t b) -- | apply an arrow element wise to all children of the root of a tree -- collect these results and substitute the children with this result -- -- example: processChildren isText deletes all subtrees, for -- which isText does not hold -- -- example: processChildren (none `when` isCmt) removes all -- children, for which isCmt holds processChildren :: (ArrowTree a, Tree t) => a (t b) (t b) -> a (t b) (t b) -- | similar to processChildren, but the new children are computed by -- processing the whole input tree -- -- example: replaceChildren (deep isText) selects all subtrees -- for which isText holds and substitutes the children component of the -- root node with this list replaceChildren :: (ArrowTree a, Tree t) => a (t b) (t b) -> a (t b) (t b) -- | pronounced "slash", meaning g inside f -- -- defined as f /> g = f >>> getChildren >>> g -- -- -- example: hasName "html" /> hasName "body" /> hasName "h1" -- -- -- This expression selects all "h1" elements in the "body" element of an -- "html" element, an expression, that corresponds 1-1 to the XPath -- selection path "html/body/h1" (/>) :: (ArrowTree a, Tree t) => a b (t c) -> a (t c) d -> a b d -- | pronounced "double slash", meaning g arbitrarily deep inside f -- -- defined as f //> g = f >>> getChildren >>> -- deep g -- -- example: hasName "html" //> hasName "table" -- -- This expression selects all top level "table" elements within an -- "html" element, an expression. Attention: This does not correspond to -- the XPath selection path "html//table". The latter on matches all -- table elements even nested ones, but //> gives in many -- cases the appropriate functionality. (//>) :: (ArrowTree a, Tree t) => a b (t c) -> a (t c) d -> a b d -- | pronounced "outside" meaning f containing g -- -- defined as f </ g = f `containing` (getChildren >>> -- g) ( a (t b) (t b) -> a (t b) (t b) -> a (t b) (t b) -- | recursively searches a whole tree for subtrees, for which a predicate -- holds. The search is performed top down. When a tree is found, this -- becomes an element of the result list. The tree found is not further -- examined for any subtress, for which the predicate also could hold. -- See multi for this kind of search. -- -- example: deep isHtmlTable selects all top level table -- elements in a document (with an appropriate definition for -- isHtmlTable) but no tables occuring within a table cell. deep :: (ArrowTree a, Tree t) => a (t b) c -> a (t b) c -- | recursively searches a whole tree for subrees, for which a predicate -- holds. The search is performed bottom up. -- -- example: deepest isHtmlTable selects all innermost table -- elements in a document but no table elements containing tables. See -- deep and multi for other search strategies. deepest :: (ArrowTree a, Tree t) => a (t b) c -> a (t b) c -- | recursively searches a whole tree for subtrees, for which a predicate -- holds. The search is performed top down. All nodes of the tree are -- searched, even within the subtrees of trees for which the predicate -- holds. -- -- example: multi isHtmlTable selects all table elements, even -- nested ones. multi :: (ArrowTree a, Tree t) => a (t b) c -> a (t b) c -- | recursively transforms a whole tree by applying an arrow to all -- subtrees, this is done bottom up depth first, leaves first, root as -- last tree -- -- example: processBottomUp (getChildren `when` isHtmlFont) -- removes all font tags in a HTML document, even nested ones (with an -- appropriate definition of isHtmlFont) processBottomUp :: (ArrowTree a, Tree t) => a (t b) (t b) -> a (t b) (t b) -- | similar to processBottomUp, but recursively transforms a whole -- tree by applying an arrow to all subtrees with a top down depth first -- traversal strategie. In many cases processBottomUp and -- processTopDown give same results. processTopDown :: (ArrowTree a, Tree t) => a (t b) (t b) -> a (t b) (t b) -- | recursively transforms a whole tree by applying an arrow to all -- subtrees, but transformation stops when a predicte does not hold for a -- subtree, leaves are transformed first processBottomUpWhenNot :: (ArrowTree a, Tree t) => a (t b) (t b) -> a (t b) (t b) -> a (t b) (t b) -- | recursively transforms a whole tree by applying an arrow to all -- subtrees, but transformation stops when a tree is successfully -- transformed. the transformation is done top down -- -- example: processTopDownUntil (isHtmlTable `guards` tranformTable) -- transforms all top level table elements into something else, but -- inner tables remain unchanged processTopDownUntil :: (ArrowTree a, Tree t) => a (t b) (t b) -> a (t b) (t b) -- | computes a list of trees by applying an arrow to the input and inserts -- this list in front of index i in the list of children -- -- example: insertChildrenAt 0 (deep isCmt) selects all -- subtrees for which isCmt holds and copies theses in front of the -- existing children insertChildrenAt :: (ArrowTree a, Tree t) => Int -> a (t b) (t b) -> a (t b) (t b) -- | similar to insertChildrenAt, but the insertion position is -- searched with a predicate insertChildrenAfter :: (ArrowTree a, Tree t) => a (t b) (t b) -> a (t b) (t b) -> a (t b) (t b) -- | an arrow for inserting a whole subtree with some holes in it (a -- template) into a document. The holes can be filled with contents from -- the input. -- -- Example -- --
--   insertTreeTemplateTest :: ArrowXml a => a b XmlTree
--   insertTreeTemplateTest
--       = doc
--         >>>
--         insertTreeTemplate template pattern
--       where
--       doc                                                                -- the input data
--          = constA "<x><y>The Title</y><z>The content</z></x>"
--            >>> xread
--       template                                                           -- the output template with 2 holes: xxx and yyy
--          = constA "<html><head><title>xxx</title></head><body><h1>yyy</h1></body></html>"
--            >>> xread
--       pattern
--          = [ hasText (== "xxx")                                          -- fill the xxx hole with the input contents from element "x/y"
--              :-> ( getChildren >>> hasName "y" >>> deep isText )
--   
--            , hasText (== "yyy")                                          -- fill the yyy hole with the input contents from element "x/z"
--              :-> ( getChildren >>> hasName "z" >>> getChildren )
--            ]
--   
-- -- computes the XML tree for the following document -- --
--   "<html><head><title>The Title</title></head><body><h1>The content</h1></body></html>"
--   
insertTreeTemplate :: (ArrowTree a, Tree t) => a (t b) (t b) -> [IfThen (a (t b) c) (a (t b) (t b))] -> a (t b) (t b) -- | The interface for trees class Tree t where mkLeaf n = mkTree n [] isLeaf = null . getChildren isInner = not . isLeaf setNode n = changeNode (const n) setChildren cl = changeChildren (const cl) nodesTree = foldTree (\ n rs -> n : concat rs) depthTree = foldTree (\ _ rs -> 1 + maximum (0 : rs)) cardTree = foldTree (\ _ rs -> 1 + sum rs) formatTree nf n = formatNTree' nf (showString "---") (showString " ") n "" -- | Implementation of pure list arrows module Control.Arrow.ListArrow -- | pure list arrow data type newtype LA a b LA :: (a -> [b]) -> LA a b [runLA] :: LA a b -> a -> [b] -- | conversion of pure list arrows into other possibly more complex list -- arrows fromLA :: ArrowList a => LA b c -> a b c instance Control.Category.Category Control.Arrow.ListArrow.LA instance Control.Arrow.Arrow Control.Arrow.ListArrow.LA instance Control.Arrow.ArrowZero Control.Arrow.ListArrow.LA instance Control.Arrow.ArrowPlus Control.Arrow.ListArrow.LA instance Control.Arrow.ArrowChoice Control.Arrow.ListArrow.LA instance Control.Arrow.ArrowApply Control.Arrow.ListArrow.LA instance Control.Arrow.ArrowList.ArrowList Control.Arrow.ListArrow.LA instance Control.Arrow.ArrowIf.ArrowIf Control.Arrow.ListArrow.LA instance Control.Arrow.ArrowTree.ArrowTree Control.Arrow.ListArrow.LA instance Control.Arrow.ArrowNavigatableTree.ArrowNavigatableTree Control.Arrow.ListArrow.LA instance Control.Arrow.ArrowNF.ArrowNF Control.Arrow.ListArrow.LA instance Control.Arrow.ArrowNF.ArrowWNF Control.Arrow.ListArrow.LA -- | arrows for efficient editing of rose trees module Control.Arrow.NTreeEdit -- | Edit parts of a rose tree -- -- The subtrees to be modified are selected by the first part of the -- IfThen pairs The modification by the second part editNTreeA :: [IfThen (LA (NTree b) c) (LA (NTree b) (NTree b))] -> LA (NTree b) (NTree b) fmapNTreeA :: (b -> Maybe b) -> LA (NTree b) (NTree b) -- | Implementation of list arrows with a state module Control.Arrow.StateListArrow -- | list arrow combined with a state newtype SLA s a b SLA :: (s -> a -> (s, [b])) -> SLA s a b [runSLA] :: SLA s a b -> s -> a -> (s, [b]) -- | conversion of state list arrows into arbitray other list arrows. -- -- allows running a state list arrow within another arrow: -- -- example: -- --
--   ... >>> fromSLA 0 (... setState ... getState ... ) >>> ...
--   
-- -- runs a state arrow with initial state 0 (e..g. an Int) within another -- arrow sequence fromSLA :: ArrowList a => s -> SLA s b c -> a b c instance Control.Category.Category (Control.Arrow.StateListArrow.SLA s) instance Control.Arrow.Arrow (Control.Arrow.StateListArrow.SLA s) instance Control.Arrow.ArrowZero (Control.Arrow.StateListArrow.SLA s) instance Control.Arrow.ArrowPlus (Control.Arrow.StateListArrow.SLA s) instance Control.Arrow.ArrowChoice (Control.Arrow.StateListArrow.SLA s) instance Control.Arrow.ArrowApply (Control.Arrow.StateListArrow.SLA s) instance Control.Arrow.ArrowList.ArrowList (Control.Arrow.StateListArrow.SLA s) instance Control.Arrow.ArrowIf.ArrowIf (Control.Arrow.StateListArrow.SLA s) instance Control.Arrow.ArrowState.ArrowState s (Control.Arrow.StateListArrow.SLA s) instance Control.Arrow.ArrowTree.ArrowTree (Control.Arrow.StateListArrow.SLA s) instance Control.Arrow.ArrowNavigatableTree.ArrowNavigatableTree (Control.Arrow.StateListArrow.SLA s) instance Control.Arrow.ArrowNF.ArrowNF (Control.Arrow.StateListArrow.SLA s) instance Control.Arrow.ArrowNF.ArrowWNF (Control.Arrow.StateListArrow.SLA s) -- | Lifting of IO actions to arrows module Control.Arrow.ArrowIO -- | the interface for converting an IO action into an arrow class Arrow a => ArrowIO a where arrIO0 f = arrIO (const f) arrIO2 f = arrIO (\ ~(x1, x2) -> f x1 x2) arrIO3 f = arrIO (\ ~(x1, ~(x2, x3)) -> f x1 x2 x3) arrIO4 f = arrIO (\ ~(x1, ~(x2, ~(x3, x4))) -> f x1 x2 x3 x4) -- | construct an arrow from an IO action arrIO :: ArrowIO a => (b -> IO c) -> a b c -- | construct an arrow from an IO action without any parameter arrIO0 :: ArrowIO a => IO c -> a b c -- | construction of a 2 argument arrow from a binary IO action | | -- example: a1 &&& a2 >>> arr2 f arrIO2 :: ArrowIO a => (b1 -> b2 -> IO c) -> a (b1, b2) c -- | construction of a 3 argument arrow from a 3-ary IO action | | example: -- a1 &&& a2 &&& a3 >>> arr3 f -- arrIO3 :: ArrowIO a => (b1 -> b2 -> b3 -> IO c) -> a (b1, (b2, b3)) c -- | construction of a 4 argument arrow from a 4-ary IO action | | example: -- a1 &&& a2 &&& a3 &&& a4 -- >>> arr4 f arrIO4 :: ArrowIO a => (b1 -> b2 -> b3 -> b4 -> IO c) -> a (b1, (b2, (b3, b4))) c -- | the interface for converting an IO predicate into a list arrow class (Arrow a, ArrowIO a) => ArrowIOIf a -- | builds an arrow from an IO predicate -- -- if the predicate holds, the single list containing the input is -- returned, else the empty list, similar to isA isIOA :: ArrowIOIf a => (b -> IO Bool) -> a b b -- | The exception arrow class module Control.Arrow.ArrowExc class (Arrow a, ArrowChoice a, ArrowZero a, ArrowIO a) => ArrowExc a where catchA f h = tryA f >>> (h ||| returnA) tryA :: ArrowExc a => a b c -> a b (Either SomeException c) catchA :: ArrowExc a => a b c -> a SomeException c -> a b c -- | Implementation of pure list arrows with IO module Control.Arrow.IOListArrow -- | list arrow combined with IO monad newtype IOLA a b IOLA :: (a -> IO [b]) -> IOLA a b [runIOLA] :: IOLA a b -> a -> IO [b] instance Control.Category.Category Control.Arrow.IOListArrow.IOLA instance Control.Arrow.Arrow Control.Arrow.IOListArrow.IOLA instance Control.Arrow.ArrowZero Control.Arrow.IOListArrow.IOLA instance Control.Arrow.ArrowPlus Control.Arrow.IOListArrow.IOLA instance Control.Arrow.ArrowChoice Control.Arrow.IOListArrow.IOLA instance Control.Arrow.ArrowApply Control.Arrow.IOListArrow.IOLA instance Control.Arrow.ArrowList.ArrowList Control.Arrow.IOListArrow.IOLA instance Control.Arrow.ArrowIf.ArrowIf Control.Arrow.IOListArrow.IOLA instance Control.Arrow.ArrowIO.ArrowIO Control.Arrow.IOListArrow.IOLA instance Control.Arrow.ArrowExc.ArrowExc Control.Arrow.IOListArrow.IOLA instance Control.Arrow.ArrowIO.ArrowIOIf Control.Arrow.IOListArrow.IOLA instance Control.Arrow.ArrowTree.ArrowTree Control.Arrow.IOListArrow.IOLA instance Control.Arrow.ArrowNavigatableTree.ArrowNavigatableTree Control.Arrow.IOListArrow.IOLA instance Control.Arrow.ArrowNF.ArrowNF Control.Arrow.IOListArrow.IOLA instance Control.Arrow.ArrowNF.ArrowWNF Control.Arrow.IOListArrow.IOLA -- | Implementation of arrows with IO and a state module Control.Arrow.IOStateListArrow -- | list arrow combined with a state and the IO monad newtype IOSLA s a b IOSLA :: (s -> a -> IO (s, [b])) -> IOSLA s a b [runIOSLA] :: IOSLA s a b -> s -> a -> IO (s, [b]) -- | lift the state of an IOSLA arrow to a state with an additional -- component. -- -- This is uesful, when running predefined IO arrows, e.g. for document -- input, in a context with a more complex state component. liftSt :: IOSLA s1 b c -> IOSLA (s1, s2) b c -- | run an arrow with augmented state in the context of a simple state -- arrow. An initial value for the new state component is needed. -- -- This is useful, when running an arrow with an extra environment -- component, e.g. for namespace handling in XML. runSt :: s2 -> IOSLA (s1, s2) b c -> IOSLA s1 b c instance Control.Category.Category (Control.Arrow.IOStateListArrow.IOSLA s) instance Control.Arrow.Arrow (Control.Arrow.IOStateListArrow.IOSLA s) instance Control.Arrow.ArrowZero (Control.Arrow.IOStateListArrow.IOSLA s) instance Control.Arrow.ArrowPlus (Control.Arrow.IOStateListArrow.IOSLA s) instance Control.Arrow.ArrowChoice (Control.Arrow.IOStateListArrow.IOSLA s) instance Control.Arrow.ArrowApply (Control.Arrow.IOStateListArrow.IOSLA s) instance Control.Arrow.ArrowList.ArrowList (Control.Arrow.IOStateListArrow.IOSLA s) instance Control.Arrow.ArrowIf.ArrowIf (Control.Arrow.IOStateListArrow.IOSLA s) instance Control.Arrow.ArrowIO.ArrowIO (Control.Arrow.IOStateListArrow.IOSLA s) instance Control.Arrow.ArrowExc.ArrowExc (Control.Arrow.IOStateListArrow.IOSLA s) instance Control.Arrow.ArrowIO.ArrowIOIf (Control.Arrow.IOStateListArrow.IOSLA s) instance Control.Arrow.ArrowState.ArrowState s (Control.Arrow.IOStateListArrow.IOSLA s) instance Control.Arrow.ArrowTree.ArrowTree (Control.Arrow.IOStateListArrow.IOSLA s) instance Control.Arrow.ArrowNavigatableTree.ArrowNavigatableTree (Control.Arrow.IOStateListArrow.IOSLA s) instance Control.Arrow.ArrowNF.ArrowNF (Control.Arrow.IOStateListArrow.IOSLA s) instance Control.Arrow.ArrowNF.ArrowWNF (Control.Arrow.IOStateListArrow.IOSLA s) -- | Basic arrows for processing XML documents -- -- All arrows use IO and a global state for options, errorhandling, ... module Text.XML.HXT.Arrow.XmlArrow -- | Arrows for processing XmlTrees -- -- These arrows can be grouped into predicates, selectors, constructors, -- and transformers. -- -- All predicates (tests) act like none for failure and -- this for success. A logical and can be formed by a1 -- >>> a2 , a locical or by a1 <+> a2 . -- -- Selector arrows will fail, when applied to wrong input, e.g. selecting -- the text of a node with getText will fail when applied to a -- none text node. -- -- Edit arrows will remain the input unchanged, when applied to wrong -- argument, e.g. editing the content of a text node with -- changeText applied to an element node will return the unchanged -- element node. class (Arrow a, ArrowList a, ArrowTree a) => ArrowXml a where isText = isA isText isBlob = isA isBlob isCharRef = isA isCharRef isEntityRef = isA isEntityRef isCmt = isA isCmt isCdata = isA isCdata isPi = isA isPi isXmlPi = isPi >>> hasName "xml" isElem = isA isElem isDTD = isA isDTD isAttr = isA isAttr isError = isA isError isRoot = isA isRoot hasText p = (isText >>> getText >>> isA p) `guards` this isWhiteSpace = hasText (all isXmlSpaceChar) hasNameWith p = (getQName >>> isA p) `guards` this hasQName n = (getQName >>> isA (== n)) `guards` this hasName n = (getName >>> isA (== n)) `guards` this hasLocalPart n = (getLocalPart >>> isA (== n)) `guards` this hasNamePrefix n = (getNamePrefix >>> isA (== n)) `guards` this hasNamespaceUri n = (getNamespaceUri >>> isA (== n)) `guards` this hasAttr n = (getAttrl >>> hasName n) `guards` this hasQAttr n = (getAttrl >>> hasQName n) `guards` this hasAttrValue n p = (getAttrl >>> hasName n >>> xshow getChildren >>> isA p) `guards` this hasQAttrValue n p = (getAttrl >>> hasQName n >>> xshow getChildren >>> isA p) `guards` this mkText = arr mkText mkBlob = arr mkBlob mkCharRef = arr mkCharRef mkEntityRef = arr mkEntityRef mkCmt = arr mkCmt mkCdata = arr mkCdata mkError level = arr (mkError level) mkElement n af cf = (listA af &&& listA cf) >>> arr2 (\ al cl -> mkElement n al cl) mkAttr qn f = listA f >>> arr (mkAttr qn) mkPi qn f = listA f >>> arr (mkPi qn) mkqelem n afs cfs = mkElement n (catA afs) (catA cfs) mkelem n afs cfs = mkElement (mkName n) (catA afs) (catA cfs) aelem n afs = catA afs >. \ al -> mkElement (mkName n) al [] selem n cfs = catA cfs >. mkElement (mkName n) [] eelem n = constA (mkElement (mkName n) [] []) root = mkelem t_root qattr = mkAttr attr = mkAttr . mkName txt = constA . mkText blb = constA . mkBlob charRef = constA . mkCharRef entityRef = constA . mkEntityRef cmt = constA . mkCmt warn = constA . (mkError c_warn) err = constA . (mkError c_err) fatal = constA . (mkError c_fatal) spi piName piCont = constA (mkPi (mkName piName) [mkAttr (mkName a_value) [mkText piCont]]) sqattr an av = constA (mkAttr an [mkText av]) sattr an av = constA (mkAttr (mkName an) [mkText av]) getText = arrL (maybeToList . getText) getCharRef = arrL (maybeToList . getCharRef) getEntityRef = arrL (maybeToList . getEntityRef) getCmt = arrL (maybeToList . getCmt) getCdata = arrL (maybeToList . getCdata) getPiName = arrL (maybeToList . getPiName) getPiContent = arrL (fromMaybe [] . getPiContent) getElemName = arrL (maybeToList . getElemName) getAttrl = arrL (fromMaybe [] . getAttrl) getDTDPart = arrL (maybeToList . getDTDPart) getDTDAttrl = arrL (maybeToList . getDTDAttrl) getAttrName = arrL (maybeToList . getAttrName) getErrorLevel = arrL (maybeToList . getErrorLevel) getErrorMsg = arrL (maybeToList . getErrorMsg) getQName = arrL (maybeToList . getName) getName = arrL (maybeToList . getQualifiedName) getUniversalName = arrL (maybeToList . getUniversalName) getUniversalUri = arrL (maybeToList . getUniversalUri) getLocalPart = arrL (maybeToList . getLocalPart) getNamePrefix = arrL (maybeToList . getNamePrefix) getNamespaceUri = arrL (maybeToList . getNamespaceUri) getAttrValue n = xshow (getAttrl >>> hasName n >>> getChildren) getAttrValue0 n = getAttrl >>> hasName n >>> xshow getChildren getQAttrValue n = xshow (getAttrl >>> hasQName n >>> getChildren) getQAttrValue0 n = getAttrl >>> hasQName n >>> xshow getChildren changeText cf = arr (changeText cf) `when` isText changeBlob cf = arr (changeBlob cf) `when` isBlob changeCmt cf = arr (changeCmt cf) `when` isCmt changeQName cf = arr (changeName cf) `when` getQName changeElemName cf = arr (changeElemName cf) `when` isElem changeAttrName cf = arr (changeAttrName cf) `when` isAttr changePiName cf = arr (changePiName cf) `when` isPi changeAttrValue cf = replaceChildren (xshow getChildren >>> arr cf >>> mkText) `when` isAttr changeAttrl cf f = ((listA f &&& this) >>> arr2 changeAL) `when` (isElem <+> isPi) where changeAL as x = changeAttrl (\ xs -> cf xs as) x setQName n = changeQName (const n) setElemName n = changeElemName (const n) setAttrName n = changeAttrName (const n) setPiName n = changePiName (const n) setAttrl = changeAttrl (const id) addAttrl = changeAttrl (mergeAttrl) addAttr an av = addAttrl (sattr an av) removeAttr an = processAttrl (none `when` hasName an) removeQAttr an = processAttrl (none `when` hasQName an) processAttrl f = setAttrl (getAttrl >>> f) processTopDownWithAttrl f = processTopDown (f >>> (processAttrl (processTopDown f) `when` isElem)) tf += cf = (tf &&& listA cf) >>> arr2 addChildren where addChildren :: XmlTree -> XmlTrees -> XmlTree addChildren t cs = foldl addChild t cs addChild :: XmlTree -> XmlTree -> XmlTree addChild t c | not (isElem t) = t | isAttr c = changeAttrl (addAttr c) t | otherwise = changeChildren (++ [c]) t xshow f = f >. xshow xshowBlob f = f >. xshowBlob -- | test for text nodes isText :: ArrowXml a => a XmlTree XmlTree isBlob :: ArrowXml a => a XmlTree XmlTree -- | test for char reference, used during parsing isCharRef :: ArrowXml a => a XmlTree XmlTree -- | test for entity reference, used during parsing isEntityRef :: ArrowXml a => a XmlTree XmlTree -- | test for comment isCmt :: ArrowXml a => a XmlTree XmlTree -- | test for CDATA section, used during parsing isCdata :: ArrowXml a => a XmlTree XmlTree -- | test for processing instruction isPi :: ArrowXml a => a XmlTree XmlTree -- | test for processing instruction <?xml ...> isXmlPi :: ArrowXml a => a XmlTree XmlTree -- | test for element isElem :: ArrowXml a => a XmlTree XmlTree -- | test for DTD part, used during parsing isDTD :: ArrowXml a => a XmlTree XmlTree -- | test for attribute tree isAttr :: ArrowXml a => a XmlTree XmlTree -- | test for error message isError :: ArrowXml a => a XmlTree XmlTree -- | test for root node (element with name "/") isRoot :: ArrowXml a => a XmlTree XmlTree -- | test for text nodes with text, for which a predicate holds -- -- example: hasText (all (`elem` " \t\n")) check for text nodes -- with only whitespace content hasText :: ArrowXml a => (String -> Bool) -> a XmlTree XmlTree -- | test for text nodes with only white space -- -- implemented with hasTest isWhiteSpace :: ArrowXml a => a XmlTree XmlTree -- | test whether a node (element, attribute, pi) has a name with a special -- property hasNameWith :: ArrowXml a => (QName -> Bool) -> a XmlTree XmlTree -- | test whether a node (element, attribute, pi) has a specific qualified -- name useful only after namespace propagation hasQName :: ArrowXml a => QName -> a XmlTree XmlTree -- | test whether a node has a specific name (prefix:localPart or -- localPart), generally useful, even without namespace handling hasName :: ArrowXml a => String -> a XmlTree XmlTree -- | test whether a node has a specific name as local part, useful only -- after namespace propagation hasLocalPart :: ArrowXml a => String -> a XmlTree XmlTree -- | test whether a node has a specific name prefix, useful only after -- namespace propagation hasNamePrefix :: ArrowXml a => String -> a XmlTree XmlTree -- | test whether a node has a specific namespace URI useful only after -- namespace propagation hasNamespaceUri :: ArrowXml a => String -> a XmlTree XmlTree -- | test whether an element node has an attribute node with a specific -- name hasAttr :: ArrowXml a => String -> a XmlTree XmlTree -- | test whether an element node has an attribute node with a specific -- qualified name hasQAttr :: ArrowXml a => QName -> a XmlTree XmlTree -- | test whether an element node has an attribute with a specific value hasAttrValue :: ArrowXml a => String -> (String -> Bool) -> a XmlTree XmlTree -- | test whether an element node has an attribute with a qualified name -- and a specific value hasQAttrValue :: ArrowXml a => QName -> (String -> Bool) -> a XmlTree XmlTree -- | text node construction arrow mkText :: ArrowXml a => a String XmlTree -- | blob node construction arrow mkBlob :: ArrowXml a => a Blob XmlTree -- | char reference construction arrow, useful for document output mkCharRef :: ArrowXml a => a Int XmlTree -- | entity reference construction arrow, useful for document output mkEntityRef :: ArrowXml a => a String XmlTree -- | comment node construction, useful for document output mkCmt :: ArrowXml a => a String XmlTree -- | CDATA construction, useful for document output mkCdata :: ArrowXml a => a String XmlTree -- | error node construction, useful only internally mkError :: ArrowXml a => Int -> a String XmlTree -- | element construction: | the attributes and the content of the element -- are computed by applying arrows to the input mkElement :: ArrowXml a => QName -> a n XmlTree -> a n XmlTree -> a n XmlTree -- | attribute node construction: | the attribute value is computed by -- applying an arrow to the input mkAttr :: ArrowXml a => QName -> a n XmlTree -> a n XmlTree -- | processing instruction construction: | the content of the processing -- instruction is computed by applying an arrow to the input mkPi :: ArrowXml a => QName -> a n XmlTree -> a n XmlTree -- | convenient arrow for element construction, more comfortable variant of -- mkElement -- -- example for simplifying mkElement : -- --
--   mkElement qn (a1 <+> ... <+> ai) (c1 <+> ... <+> cj)
--   
-- -- equals -- --
--   mkqelem qn [a1,...,ai] [c1,...,cj]
--   
mkqelem :: ArrowXml a => QName -> [a n XmlTree] -> [a n XmlTree] -> a n XmlTree -- | convenient arrow for element construction with strings instead of -- qualified names as element names, see also mkElement and -- mkelem mkelem :: ArrowXml a => String -> [a n XmlTree] -> [a n XmlTree] -> a n XmlTree -- | convenient arrow for element constrution with attributes but without -- content, simple variant of mkelem and mkElement aelem :: ArrowXml a => String -> [a n XmlTree] -> a n XmlTree -- | convenient arrow for simple element constrution without attributes, -- simple variant of mkelem and mkElement selem :: ArrowXml a => String -> [a n XmlTree] -> a n XmlTree -- | convenient arrow for constrution of empty elements without attributes, -- simple variant of mkelem and mkElement eelem :: ArrowXml a => String -> a n XmlTree -- | construction of an element node with name "/" for document roots root :: ArrowXml a => [a n XmlTree] -> [a n XmlTree] -> a n XmlTree -- | alias for mkAttr qattr :: ArrowXml a => QName -> a n XmlTree -> a n XmlTree -- | convenient arrow for attribute constrution, simple variant of -- mkAttr attr :: ArrowXml a => String -> a n XmlTree -> a n XmlTree -- | constant arrow for text nodes txt :: ArrowXml a => String -> a n XmlTree -- | constant arrow for blob nodes blb :: ArrowXml a => Blob -> a n XmlTree -- | constant arrow for char reference nodes charRef :: ArrowXml a => Int -> a n XmlTree -- | constant arrow for entity reference nodes entityRef :: ArrowXml a => String -> a n XmlTree -- | constant arrow for comment cmt :: ArrowXml a => String -> a n XmlTree -- | constant arrow for warning warn :: ArrowXml a => String -> a n XmlTree -- | constant arrow for errors err :: ArrowXml a => String -> a n XmlTree -- | constant arrow for fatal errors fatal :: ArrowXml a => String -> a n XmlTree -- | constant arrow for simple processing instructions, see mkPi spi :: ArrowXml a => String -> String -> a n XmlTree -- | constant arrow for attribute nodes, attribute name is a qualified name -- and value is a text, | see also mkAttr, qattr, -- attr sqattr :: ArrowXml a => QName -> String -> a n XmlTree -- | constant arrow for attribute nodes, attribute name and value are | -- given by parameters, see mkAttr sattr :: ArrowXml a => String -> String -> a n XmlTree -- | select the text of a text node getText :: ArrowXml a => a XmlTree String -- | select the value of a char reference getCharRef :: ArrowXml a => a XmlTree Int -- | select the name of a entity reference node getEntityRef :: ArrowXml a => a XmlTree String -- | select the comment of a comment node getCmt :: ArrowXml a => a XmlTree String -- | select the content of a CDATA node getCdata :: ArrowXml a => a XmlTree String -- | select the name of a processing instruction getPiName :: ArrowXml a => a XmlTree QName -- | select the content of a processing instruction getPiContent :: ArrowXml a => a XmlTree XmlTree -- | select the name of an element node getElemName :: ArrowXml a => a XmlTree QName -- | select the attribute list of an element node getAttrl :: ArrowXml a => a XmlTree XmlTree -- | select the DTD type of a DTD node getDTDPart :: ArrowXml a => a XmlTree DTDElem -- | select the DTD attributes of a DTD node getDTDAttrl :: ArrowXml a => a XmlTree Attributes -- | select the name of an attribute getAttrName :: ArrowXml a => a XmlTree QName -- | select the error level (c_warn, c_err, c_fatal) from an error node getErrorLevel :: ArrowXml a => a XmlTree Int -- | select the error message from an error node getErrorMsg :: ArrowXml a => a XmlTree String -- | select the qualified name from an element, attribute or pi getQName :: ArrowXml a => a XmlTree QName -- | select the prefix:localPart or localPart from an element, attribute or -- pi getName :: ArrowXml a => a XmlTree String -- | select the univeral name ({namespace URI} ++ localPart) getUniversalName :: ArrowXml a => a XmlTree String -- | select the univeral name (namespace URI ++ localPart) getUniversalUri :: ArrowXml a => a XmlTree String -- | select the local part getLocalPart :: ArrowXml a => a XmlTree String -- | select the name prefix getNamePrefix :: ArrowXml a => a XmlTree String -- | select the namespace URI getNamespaceUri :: ArrowXml a => a XmlTree String -- | select the value of an attribute of an element node, always succeeds -- with empty string as default value "" getAttrValue :: ArrowXml a => String -> a XmlTree String -- | like getAttrValue, but fails if the attribute does not exist getAttrValue0 :: ArrowXml a => String -> a XmlTree String -- | like getAttrValue, but select the value of an attribute given -- by a qualified name, always succeeds with empty string as default -- value "" getQAttrValue :: ArrowXml a => QName -> a XmlTree String -- | like getQAttrValue, but fails if attribute does not exist getQAttrValue0 :: ArrowXml a => QName -> a XmlTree String -- | edit the string of a text node changeText :: ArrowXml a => (String -> String) -> a XmlTree XmlTree -- | edit the blob of a blob node changeBlob :: ArrowXml a => (Blob -> Blob) -> a XmlTree XmlTree -- | edit the comment string of a comment node changeCmt :: ArrowXml a => (String -> String) -> a XmlTree XmlTree -- | edit an element-, attribute- or pi- name changeQName :: ArrowXml a => (QName -> QName) -> a XmlTree XmlTree -- | edit an element name changeElemName :: ArrowXml a => (QName -> QName) -> a XmlTree XmlTree -- | edit an attribute name changeAttrName :: ArrowXml a => (QName -> QName) -> a XmlTree XmlTree -- | edit a pi name changePiName :: ArrowXml a => (QName -> QName) -> a XmlTree XmlTree -- | edit an attribute value changeAttrValue :: ArrowXml a => (String -> String) -> a XmlTree XmlTree -- | edit an attribute list of an element node changeAttrl :: ArrowXml a => (XmlTrees -> XmlTrees -> XmlTrees) -> a XmlTree XmlTree -> a XmlTree XmlTree -- | replace an element, attribute or pi name setQName :: ArrowXml a => QName -> a XmlTree XmlTree -- | replace an element name setElemName :: ArrowXml a => QName -> a XmlTree XmlTree -- | replace an attribute name setAttrName :: ArrowXml a => QName -> a XmlTree XmlTree -- | replace an element name setPiName :: ArrowXml a => QName -> a XmlTree XmlTree -- | replace an atribute list of an element node setAttrl :: ArrowXml a => a XmlTree XmlTree -> a XmlTree XmlTree -- | add a list of attributes to an element addAttrl :: ArrowXml a => a XmlTree XmlTree -> a XmlTree XmlTree -- | add (or replace) an attribute addAttr :: ArrowXml a => String -> String -> a XmlTree XmlTree -- | remove an attribute removeAttr :: ArrowXml a => String -> a XmlTree XmlTree -- | remove an attribute with a qualified name removeQAttr :: ArrowXml a => QName -> a XmlTree XmlTree -- | process the attributes of an element node with an arrow processAttrl :: ArrowXml a => a XmlTree XmlTree -> a XmlTree XmlTree -- | process a whole tree inclusive attribute list of element nodes see -- also: processTopDown processTopDownWithAttrl :: ArrowXml a => a XmlTree XmlTree -> a XmlTree XmlTree -- | convenient op for adding attributes or children to a node -- -- usage: tf += cf -- -- the tf arrow computes an element node, and all trees computed -- by cf are added to this node, if a tree is an attribute, it -- is inserted in the attribute list else it is appended to the content -- list. -- -- attention: do not build long content list this way because += -- is implemented by ++ -- -- examples: -- --
--   eelem "a"
--     += sattr "href" "page.html"
--     += sattr "name" "here"
--     += txt "look here"
--   
-- -- is the same as -- --
--   mkelem [ sattr "href" "page.html"
--          , sattr "name" "here"
--          ]
--          [ txt "look here" ]
--   
-- -- and results in the XML fragment: <a href="page.html" -- name="here">look here</a> -- -- advantage of the += operator is, that attributes and content -- can be added any time step by step. if tf computes a whole -- list of trees, e.g. a list of "td" or "tr" elements, the attributes or -- content is added to all trees. useful for adding "class" or "style" -- attributes to table elements. (+=) :: ArrowXml a => a b XmlTree -> a b XmlTree -> a b XmlTree -- | apply an arrow to the input and convert the resulting XML trees into a -- string representation xshow :: ArrowXml a => a n XmlTree -> a n String -- | apply an arrow to the input and convert the resulting XML trees into a -- string representation xshowBlob :: ArrowXml a => a n XmlTree -> a n Blob -- | Document Type Definition arrows -- -- These are separated, because they are not needed for document -- processing, only when processing the DTD, e.g. for generating access -- funtions for the toolbox from a DTD (se example DTDtoHaskell in the -- examples directory) class (ArrowXml a) => ArrowDTD a where isDTDDoctype = isA (maybe False (== DOCTYPE) . getDTDPart) isDTDElement = isA (maybe False (== ELEMENT) . getDTDPart) isDTDContent = isA (maybe False (== CONTENT) . getDTDPart) isDTDAttlist = isA (maybe False (== ATTLIST) . getDTDPart) isDTDEntity = isA (maybe False (== ENTITY) . getDTDPart) isDTDPEntity = isA (maybe False (== PENTITY) . getDTDPart) isDTDNotation = isA (maybe False (== NOTATION) . getDTDPart) isDTDCondSect = isA (maybe False (== CONDSECT) . getDTDPart) isDTDName = isA (maybe False (== NAME) . getDTDPart) isDTDPERef = isA (maybe False (== PEREF) . getDTDPart) hasDTDAttr n = isA (isJust . lookup n . fromMaybe [] . getDTDAttrl) getDTDAttrValue n = arrL (maybeToList . lookup n . fromMaybe [] . getDTDAttrl) setDTDAttrValue n v = arr (changeDTDAttrl (addEntry n v)) `when` isDTD mkDTDElem e al cf = listA cf >>> arr (mkDTDElem e al) mkDTDDoctype = mkDTDElem DOCTYPE mkDTDElement al = mkDTDElem ELEMENT al none mkDTDEntity al = mkDTDElem ENTITY al none mkDTDPEntity al = mkDTDElem PENTITY al none isDTDDoctype :: ArrowDTD a => a XmlTree XmlTree isDTDElement :: ArrowDTD a => a XmlTree XmlTree isDTDContent :: ArrowDTD a => a XmlTree XmlTree isDTDAttlist :: ArrowDTD a => a XmlTree XmlTree isDTDEntity :: ArrowDTD a => a XmlTree XmlTree isDTDPEntity :: ArrowDTD a => a XmlTree XmlTree isDTDNotation :: ArrowDTD a => a XmlTree XmlTree isDTDCondSect :: ArrowDTD a => a XmlTree XmlTree isDTDName :: ArrowDTD a => a XmlTree XmlTree isDTDPERef :: ArrowDTD a => a XmlTree XmlTree hasDTDAttr :: ArrowDTD a => String -> a XmlTree XmlTree getDTDAttrValue :: ArrowDTD a => String -> a XmlTree String setDTDAttrValue :: ArrowDTD a => String -> String -> a XmlTree XmlTree mkDTDElem :: ArrowDTD a => DTDElem -> Attributes -> a n XmlTree -> a n XmlTree mkDTDDoctype :: ArrowDTD a => Attributes -> a n XmlTree -> a n XmlTree mkDTDElement :: ArrowDTD a => Attributes -> a n XmlTree mkDTDEntity :: ArrowDTD a => Attributes -> a n XmlTree mkDTDPEntity :: ArrowDTD a => Attributes -> a n XmlTree instance Text.XML.HXT.Arrow.XmlArrow.ArrowXml Control.Arrow.ListArrow.LA instance Text.XML.HXT.Arrow.XmlArrow.ArrowXml (Control.Arrow.StateListArrow.SLA s) instance Text.XML.HXT.Arrow.XmlArrow.ArrowXml Control.Arrow.IOListArrow.IOLA instance Text.XML.HXT.Arrow.XmlArrow.ArrowXml (Control.Arrow.IOStateListArrow.IOSLA s) instance Text.XML.HXT.Arrow.XmlArrow.ArrowDTD Control.Arrow.ListArrow.LA instance Text.XML.HXT.Arrow.XmlArrow.ArrowDTD (Control.Arrow.StateListArrow.SLA s) instance Text.XML.HXT.Arrow.XmlArrow.ArrowDTD Control.Arrow.IOListArrow.IOLA instance Text.XML.HXT.Arrow.XmlArrow.ArrowDTD (Control.Arrow.IOStateListArrow.IOSLA s) -- | common edit arrows module Text.XML.HXT.Arrow.Edit -- | Applies some "Canonical XML" rules to a document tree. -- -- The rule differ slightly for canonical XML and XPath in handling of -- comments -- -- Note: This is not the whole canonicalization as it is specified by the -- W3C Recommendation. Adding attribute defaults or sorting attributes in -- lexicographic order is done by the transform function of -- module Text.XML.HXT.Validator.Validation. Replacing entities -- or line feed normalization is done by the parser. -- -- Rules: remove DTD parts, processing instructions, comments and -- substitute char refs in attribute values and text -- -- Not implemented yet: -- -- canonicalizeAllNodes :: ArrowList a => a XmlTree XmlTree -- | Canonicalize a tree for XPath Like canonicalizeAllNodes but -- comment nodes are not removed -- -- see canonicalizeAllNodes canonicalizeForXPath :: ArrowList a => a XmlTree XmlTree -- | Canonicalize the contents of a document -- -- substitutes all char refs in text and attribute values, removes CDATA -- section and combines all sequences of resulting text nodes into a -- single text node -- -- see canonicalizeAllNodes canonicalizeContents :: ArrowList a => a XmlTree XmlTree -- | Applies collapseXText recursively. -- -- see also : collapseXText collapseAllXText :: ArrowList a => a XmlTree XmlTree -- | Collects sequences of text nodes in the list of children of a node -- into one single text node. This is useful, e.g. after char and entity -- reference substitution collapseXText :: ArrowList a => a XmlTree XmlTree -- | apply an arrow to the input and convert the resulting XML trees into -- an XML escaped string -- -- This is a save variant for converting a tree into an XML string -- representation that is parsable with ReadDocument. It is -- implemented with xshow, but xshow does no XML escaping. The XML -- escaping is done with escapeXmlDoc before xshow is applied. -- -- So the following law holds -- --
--   xshowEscapeXml f >>> xread == f
--   
xshowEscapeXml :: ArrowXml a => a n XmlTree -> a n String escapeXmlRefs :: (Char -> String -> String, Char -> String -> String) escapeHtmlRefs :: (Char -> String -> String, Char -> String -> String) -- | convert a document into a Haskell representation (with show). -- -- Useful for debugging and trace output. see also : -- treeRepOfXmlDoc, numberLinesInXmlDoc haskellRepOfXmlDoc :: ArrowList a => a XmlTree XmlTree -- | convert a document into a text representation in tree form. -- -- Useful for debugging and trace output. see also : -- haskellRepOfXmlDoc, numberLinesInXmlDoc treeRepOfXmlDoc :: ArrowList a => a XmlTree XmlTree addHeadlineToXmlDoc :: ArrowXml a => a XmlTree XmlTree -- | filter for indenting a document tree for pretty printing. -- -- the tree is traversed for inserting whitespace for tag indentation. -- -- whitespace is only inserted or changed at places, where it isn't -- significant, is's not inserted between tags and text containing non -- whitespace chars. -- -- whitespace is only inserted or changed at places, where it's not -- significant. preserving whitespace may be controlled in a document -- tree by a tag attribute xml:space -- -- allowed values for this attribute are default | preserve. -- -- input is a complete document tree or a document fragment result is the -- semantically equivalent formatted tree. -- -- see also : removeDocWhiteSpace indentDoc :: ArrowXml a => a XmlTree XmlTree -- | convert a document into a text and add line numbers to the text -- representation. -- -- Result is a root node with a single text node as child. Useful for -- debugging and trace output. see also : haskellRepOfXmlDoc, -- treeRepOfXmlDoc numberLinesInXmlDoc :: ArrowList a => a XmlTree XmlTree preventEmptyElements :: ArrowList a => [String] -> Bool -> a XmlTree XmlTree -- | remove a Comment node removeComment :: ArrowXml a => a XmlTree XmlTree -- | remove all comments in a tree recursively removeAllComment :: ArrowXml a => a XmlTree XmlTree -- | simple filter for removing whitespace. -- -- no check on sigificant whitespace, e.g. in HTML <pre>-elements, -- is done. -- -- see also : removeAllWhiteSpace, removeDocWhiteSpace removeWhiteSpace :: ArrowXml a => a XmlTree XmlTree -- | simple recursive filter for removing all whitespace. -- -- removes all text nodes in a tree that consist only of whitespace. -- -- see also : removeWhiteSpace, removeDocWhiteSpace removeAllWhiteSpace :: ArrowXml a => a XmlTree XmlTree -- | filter for removing all not significant whitespace. -- -- the tree traversed for removing whitespace between elements, that was -- inserted for indentation and readability. whitespace is only removed -- at places, where it's not significat preserving whitespace may be -- controlled in a document tree by a tag attribute xml:space -- -- allowed values for this attribute are default | preserve -- -- input is root node of the document to be cleaned up, output the -- semantically equivalent simplified tree -- -- see also : indentDoc, removeAllWhiteSpace removeDocWhiteSpace :: ArrowXml a => a XmlTree XmlTree -- | converts a CDATA section into normal text nodes transfCdata :: ArrowXml a => a XmlTree XmlTree -- | converts CDATA sections in whole document tree into normal text nodes transfAllCdata :: ArrowXml a => a XmlTree XmlTree -- | converts a character reference to normal text transfCharRef :: ArrowXml a => a XmlTree XmlTree -- | recursively converts all character references to normal text transfAllCharRef :: ArrowXml a => a XmlTree XmlTree substAllXHTMLEntityRefs :: ArrowXml a => a XmlTree XmlTree substXHTMLEntityRef :: LA XmlTree XmlTree rememberDTDAttrl :: ArrowList a => a XmlTree XmlTree addDefaultDTDecl :: ArrowList a => a XmlTree XmlTree hasXmlPi :: ArrowXml a => a XmlTree XmlTree -- | add an <?xml version="1.0"?> processing instruction if it's not -- already there addXmlPi :: ArrowXml a => a XmlTree XmlTree -- | add an encoding spec to the <?xml version="1.0"?> processing -- instruction addXmlPiEncoding :: ArrowXml a => String -> a XmlTree XmlTree -- | add a doctype declaration to a document -- -- The arguments are the root element name, the PUBLIC id and the SYSTEM -- id addDoctypeDecl :: ArrowXml a => String -> String -> String -> a XmlTree XmlTree -- | add an XHTML strict doctype declaration to a document -- -- add an XHTML strict doctype declaration to a document addXHtmlDoctypeStrict :: ArrowXml a => a XmlTree XmlTree -- | add an XHTML transitional doctype declaration to a document -- -- add an XHTML strict doctype declaration to a document addXHtmlDoctypeTransitional :: ArrowXml a => a XmlTree XmlTree -- | add an XHTML frameset doctype declaration to a document -- -- add an XHTML strict doctype declaration to a document addXHtmlDoctypeFrameset :: ArrowXml a => a XmlTree XmlTree -- | namespace specific arrows module Text.XML.HXT.Arrow.Namespace -- | attach all valid namespace declarations to the attribute list of -- element nodes. -- -- This arrow is useful for document processing, that requires access to -- all namespace declarations at any element node, but which cannot be -- done with a simple processWithNsEnv. attachNsEnv :: ArrowXml a => NsEnv -> a XmlTree XmlTree -- | does the real work for namespace cleanup. -- -- The parameter is used for collecting namespace uris and prefixes from -- the input tree cleanupNamespaces :: LA XmlTree (String, String) -> LA XmlTree XmlTree -- | collect all namespace declarations contained in a document -- -- apply getNamespaceDecl to a whole XmlTree collectNamespaceDecl :: LA XmlTree (String, String) -- | collect all (namePrefix, namespaceUri) pairs from a tree -- -- all qualified names are inspected, whether a namespace uri is defined, -- for these uris the prefix and uri is returned. This arrow is useful -- for namespace cleanup, e.g. for documents generated with XSLT. It can -- be used together with collectNamespaceDecl to -- cleanupNamespaces collectPrefixUriPairs :: LA XmlTree (String, String) -- | test whether an attribute node contains an XML Namespace declaration isNamespaceDeclAttr :: ArrowXml a => a XmlTree XmlTree -- | get the namespace prefix and the namespace URI out of an attribute -- tree with a namespace declaration (see isNamespaceDeclAttr) for -- all other nodes this arrow fails getNamespaceDecl :: ArrowXml a => a XmlTree (String, String) -- | process a document tree with an arrow, containing always the valid -- namespace environment as extra parameter. -- -- The namespace environment is implemented as a AssocList processWithNsEnv :: ArrowXml a => (NsEnv -> a XmlTree XmlTree) -> NsEnv -> a XmlTree XmlTree -- | process all element nodes of a document tree with an arrow, containing -- always the valid namespace environment as extra parameter. Attribute -- lists are not processed. -- -- See also: processWithNsEnv processWithNsEnvWithoutAttrl :: ArrowXml a => (NsEnv -> a XmlTree XmlTree) -> NsEnv -> a XmlTree XmlTree -- | propagate all namespace declarations "xmlns:ns=..." to all element and -- attribute nodes of a document. -- -- This arrow does not check for illegal use of namespaces. The real work -- is done by propagateNamespaceEnv. -- -- The arrow may be applied repeatedly if neccessary. propagateNamespaces :: ArrowXml a => a XmlTree XmlTree -- | generate unique namespaces and add all namespace declarations to all -- top nodes containing a namespace declaration Usually the top node -- containing namespace declarations is the root node, but this isn't -- mandatory. -- -- Calls cleanupNamespaces with collectNamespaceDecl uniqueNamespaces :: ArrowXml a => a XmlTree XmlTree -- | generate unique namespaces and add all namespace declarations for all -- prefix-uri pairs in all qualified names -- -- useful for cleanup of namespaces in generated documents. Calls -- cleanupNamespaces with collectNamespaceDecl <+> -- collectPrefixUriPairs uniqueNamespacesFromDeclAndQNames :: ArrowXml a => a XmlTree XmlTree -- | validate the namespace constraints in a whole tree. -- -- Result is the list of errors concerning namespaces. Predicates -- isWellformedQName, isWellformedQualifiedName, -- isDeclaredNamespace and isWellformedNSDecl are applied -- to the appropriate elements and attributes. validateNamespaces :: ArrowXml a => a XmlTree XmlTree -- | interface to the HXT XML and DTD parsers module Text.XML.HXT.Arrow.ParserInterface parseXmlDoc :: ArrowXml a => a (String, String) XmlTree parseXmlDTDPart :: ArrowXml a => a (String, XmlTree) XmlTree xreadCont :: ArrowXml a => a String XmlTree xreadDoc :: ArrowXml a => a String XmlTree parseXmlEntityEncodingSpec :: ArrowXml a => a XmlTree XmlTree parseXmlDocEncodingSpec :: ArrowXml a => a XmlTree XmlTree removeEncodingSpec :: ArrowXml a => a XmlTree XmlTree parseXmlDTDdeclPart :: ArrowXml a => a XmlTree XmlTree parseXmlDTDdecl :: ArrowXml a => a XmlTree XmlTree parseXmlDTDEntityValue :: ArrowXml a => a XmlTree XmlTree parseXmlEntityValueAsContent :: ArrowXml a => String -> a XmlTree XmlTree parseXmlEntityValueAsAttrValue :: ArrowXml a => String -> a XmlTree XmlTree parseHtmlDoc :: ArrowList a => a (String, String) XmlTree hread :: ArrowList a => a String XmlTree hreadDoc :: ArrowList a => a String XmlTree -- | This module provides all datatypes for DTD validation module Text.XML.HXT.DTDValidation.TypeDefs type XmlArrow = LA XmlTree XmlTree type XmlArrowS = LA XmlTree XmlTrees dtd_name :: Attributes -> String dtd_value :: Attributes -> String dtd_type :: Attributes -> String dtd_kind :: Attributes -> String dtd_modifier :: Attributes -> String dtd_default :: Attributes -> String isUnparsedEntity :: ArrowDTD a => a XmlTree XmlTree hasDTDAttrValue :: ArrowDTD a => String -> (String -> Bool) -> a XmlTree XmlTree isRequiredAttrKind :: ArrowDTD a => a XmlTree XmlTree isDefaultAttrKind :: ArrowDTD a => a XmlTree XmlTree isFixedAttrKind :: ArrowDTD a => a XmlTree XmlTree isMixedContentElement :: ArrowDTD a => a XmlTree XmlTree isEmptyElement :: ArrowDTD a => a XmlTree XmlTree isEnumAttrType :: ArrowDTD a => a XmlTree XmlTree isIdAttrType :: ArrowDTD a => a XmlTree XmlTree isIdRefAttrType :: ArrowDTD a => a XmlTree XmlTree isNotationAttrType :: ArrowDTD a => a XmlTree XmlTree isAttlistOfElement :: ArrowDTD a => String -> a XmlTree XmlTree valueOfDTD :: String -> XmlTree -> String valueOf :: String -> XmlTree -> String getDTDAttributes :: XmlTree -> Attributes isDTDDoctypeNode :: XmlTree -> Bool isDTDElementNode :: XmlTree -> Bool isDTDAttlistNode :: XmlTree -> Bool isDTDContentNode :: XmlTree -> Bool isDTDNameNode :: XmlTree -> Bool isElemNode :: XmlTree -> Bool nameOfAttr :: XmlTree -> String nameOfElem :: XmlTree -> String -- | infix operator for applying an arrow to a list of trees -- -- ($$) :: XmlArrow -> XmlTrees -> XmlTrees infixr 0 $$ -- | create an error message msgToErr :: (String -> String) -> LA String XmlTree -- | This module provides functions for validating attributes. -- -- The main functions are: -- -- module Text.XML.HXT.DTDValidation.AttributeValueValidation -- | Checks if the attribute value meets the lexical constraints of its -- type. -- -- checkAttributeValue :: XmlTrees -> XmlTree -> XmlArrow -- | Normalizes an attribute value with respect to its type. (3.3.3 / p.29 -- in Spec) -- -- normalizeAttributeValue :: Maybe XmlTree -> String -> String -- | This module provides functions for validating the DTD of XML documents -- represented as XmlTree. -- -- Unlike other popular XML validation tools the validation process -- returns a list of errors instead of aborting after the first error was -- found. -- -- Unlike validation of the document, the DTD branch is traversed four -- times: -- -- module Text.XML.HXT.DTDValidation.DTDValidation -- | Removes doublicate declarations from the DTD, which first declaration -- is binding. This is the case for ATTLIST and ENTITY declarations. -- -- removeDoublicateDefs :: XmlArrow -- | Validate a DTD. -- -- validateDTD :: XmlArrow -- | This module provides functions for transforming XML documents -- represented as XmlTree with respect to its DTD. -- -- Transforming an XML document with respect to its DTD means: -- -- -- -- Note: Transformation should be started after validation. -- -- Before the document is validated, a lookup-table is build on the basis -- of the DTD which maps element names to their transformation functions. -- After this initialization phase the whole document is traversed in -- preorder and every element is transformed by the XmlFilter from the -- lookup-table. module Text.XML.HXT.DTDValidation.DocTransformation -- | filter for transforming the document. -- -- transform :: XmlTree -> XmlArrow -- | This module provides functions for checking special -- IDIDREFIDREFS constraints. -- -- Checking special ID/IDREF/IDREFS constraints means: -- -- -- -- ID-Validation should be started before or after validating the -- document. -- -- First all nodes with ID attributes are collected from the document, -- then it is validated that values of ID attributes do not occure more -- than once. During a second iteration over the document it is validated -- that there exists an ID attribute value for IDREF/IDREFS attribute -- values. module Text.XML.HXT.DTDValidation.IdValidation -- | Perform the validation of the IDIDREFIDREFS constraints. -- -- validateIds :: XmlTree -> XmlArrow -- | A module for regular expression matching, adapted for XML DTDs. -- -- This module is based on the module RE. module Text.XML.HXT.DTDValidation.XmlRE -- | Data type for regular expressions. data RE a -- | Checks if an input matched a regular expression. The function should -- be called after matches. -- -- Was the sentence used in matches in the language of the -- regular expression? -> matches e s == s `in` L(e)? -- -- checkRE :: (Eq a, Show a) => RE a -> String -- | Derives a regular expression with respect to a list of elements. -- -- matches :: RE String -> XmlTrees -> RE String -- | Constructs a string representation of a regular expression. -- -- printRE :: (Eq a, Show a) => RE a -> String -- | Constructs a regular expression for an empty sequence. -- -- re_unit :: RE a -- | Constructs a regular expression for an empty set. -- -- re_zero :: String -> RE a -- | Constructs a regular expression for accepting a symbol -- -- re_sym :: a -> RE a -- | Constructs an optional repetition (*) of a regular expression -- -- re_rep :: RE a -> RE a -- | Constructs a repetition (+) of a regular expression -- -- re_plus :: RE a -> RE a -- | Constructs an option (?) of a regular expression -- -- re_opt :: (Ord a) => RE a -> RE a -- | Constructs a sequence (,) of two regular expressions -- -- re_seq :: RE a -> RE a -> RE a -- | Constructs an alternative (|) of two regular expressions -- -- re_alt :: (Ord a) => RE a -> RE a -> RE a -- | Constructs a regular expression for accepting any singel symbol -- -- re_dot :: RE a -- | This module provides functions for validating XML Documents -- represented as XmlTree. -- -- Unlike other popular XML validation tools the validation process -- returns a list of errors instead of aborting after the first error was -- found. -- -- Before the document is validated, a lookup-table is build on the basis -- of the DTD which maps element names to their validation functions. -- After this initialization phase the whole document is traversed in -- preorder and every element is validated by the XmlFilter from the -- lookup-table. module Text.XML.HXT.DTDValidation.DocValidation -- | Validate a document. -- -- validateDoc :: XmlTree -> XmlArrow -- | This module provides functions for validating XML documents -- represented as XmlTree. -- -- Unlike other popular XML validation tools the validation functions -- return a list of errors instead of aborting after the first error was -- found. -- -- Note: The validation process has been split into validation and -- transformation! If validate did not report any errors, -- transform should be called, to change the document the way a -- validating parser is expected to do. module Text.XML.HXT.DTDValidation.Validation getDTDSubset :: XmlArrow generalEntitiesDefined :: XmlArrow -- | Main validation filter. Check if the DTD and the document are valid. -- -- validate :: XmlArrow -- | Check if the DTD is valid. -- -- validateDTD :: XmlArrow -- | Check if the document corresponds to the given DTD. -- -- validateDoc :: XmlArrow -- | Removes doublicate declarations from the DTD which first declaration -- is binding. This is the case for ATTLIST and ENTITY declarations. -- -- removeDoublicateDefs :: XmlArrow -- | filter for transforming a document with respect to the given DTD. -- -- Validating parsers are expected to normalize attribute values and add -- default values. This function should be called after a successful -- validation. -- -- transform :: XmlArrow -- | the basic state arrows for XML processing -- -- A state is needed for global processing options, like encoding -- options, document base URI, trace levels and error message handling -- -- The state is separated into a user defined state and a system state. -- The system state contains variables for error message handling, for -- tracing, for the document base for accessing XML documents with -- relative references, e.g. DTDs, and a global key value store. This -- assoc list has strings as keys and lists of XmlTrees as values. It is -- used to store arbitrary XML and text values, e.g. user defined global -- options. -- -- The user defined part of the store is in the default case empty, -- defined as (). It can be extended with an arbitray data type module Text.XML.HXT.Arrow.XmlState.TypeDefs -- | state datatype consists of a system state and a user state the user -- state is not fixed data XIOState us XIOState :: !XIOSysState -> !us -> XIOState us [xioSysState] :: XIOState us -> !XIOSysState [xioUserState] :: XIOState us -> !us -- | The arrow type for stateful arrows type IOStateArrow s b c = IOSLA (XIOState s) b c -- | The arrow for stateful arrows with no user defined state type IOSArrow b c = IOStateArrow () b c -- | read the user defined part of the state getUserState :: IOStateArrow s b s -- | change the user defined part of the state changeUserState :: (b -> s -> s) -> IOStateArrow s b b -- | set the user defined part of the state setUserState :: IOStateArrow s s s -- | extend user state -- -- Run an arrow with an extended user state component, The old component -- is stored together with a new one in a pair, the arrow is executed -- with this extended state, and the augmented state component is removed -- form the state when the arrow has finished its execution withExtendedUserState :: s1 -> IOStateArrow (s1, s0) b c -> IOStateArrow s0 b c -- | change the type of user state -- -- This conversion is useful, when running a state arrow with another -- structure of the user state, e.g. with () when executing some IO -- arrows withOtherUserState :: s1 -> IOStateArrow s1 b c -> IOStateArrow s0 b c withoutUserState :: IOSArrow b c -> IOStateArrow s0 b c -- | predefined system state data type with all components for the system -- functions, like trace, error handling, ... data XIOSysState XIOSys :: !XIOSysWriter -> !XIOSysEnv -> XIOSysState [xioSysWriter] :: XIOSysState -> !XIOSysWriter [xioSysEnv] :: XIOSysState -> !XIOSysEnv data XIOSysWriter XIOwrt :: !Int -> !XmlTrees -> IOSArrow XmlTree XmlTree -> !Int -> !Int -> AssocList String XmlTrees -> XIOSysWriter [xioErrorStatus] :: XIOSysWriter -> !Int [xioErrorMsgList] :: XIOSysWriter -> !XmlTrees [xioExpatErrors] :: XIOSysWriter -> IOSArrow XmlTree XmlTree [xioRelaxNoOfErrors] :: XIOSysWriter -> !Int [xioRelaxDefineId] :: XIOSysWriter -> !Int [xioRelaxAttrList] :: XIOSysWriter -> AssocList String XmlTrees data XIOSysEnv XIOEnv :: !Int -> (Int -> String -> IO ()) -> (String -> IO ()) -> !Bool -> !String -> !String -> !Attributes -> !XIOInputConfig -> !XIOParseConfig -> !XIOOutputConfig -> !XIORelaxConfig -> !XIOXmlSchemaConfig -> !XIOCacheConfig -> XIOSysEnv [xioTraceLevel] :: XIOSysEnv -> !Int [xioTraceCmd] :: XIOSysEnv -> Int -> String -> IO () [xioErrorMsgHandler] :: XIOSysEnv -> String -> IO () [xioErrorMsgCollect] :: XIOSysEnv -> !Bool [xioBaseURI] :: XIOSysEnv -> !String [xioDefaultBaseURI] :: XIOSysEnv -> !String [xioAttrList] :: XIOSysEnv -> !Attributes [xioInputConfig] :: XIOSysEnv -> !XIOInputConfig [xioParseConfig] :: XIOSysEnv -> !XIOParseConfig [xioOutputConfig] :: XIOSysEnv -> !XIOOutputConfig [xioRelaxConfig] :: XIOSysEnv -> !XIORelaxConfig [xioXmlSchemaConfig] :: XIOSysEnv -> !XIOXmlSchemaConfig [xioCacheConfig] :: XIOSysEnv -> !XIOCacheConfig data XIOInputConfig XIOIcgf :: !Bool -> !Bool -> String -> IOSArrow XmlTree XmlTree -> !Attributes -> !Bool -> String -> XIOInputConfig [xioStrictInput] :: XIOInputConfig -> !Bool [xioEncodingErrors] :: XIOInputConfig -> !Bool [xioInputEncoding] :: XIOInputConfig -> String [xioHttpHandler] :: XIOInputConfig -> IOSArrow XmlTree XmlTree [xioInputOptions] :: XIOInputConfig -> !Attributes [xioRedirect] :: XIOInputConfig -> !Bool [xioProxy] :: XIOInputConfig -> String data XIOParseConfig XIOPcfg :: MimeTypeTable -> MimeTypeHandlers -> String -> [String] -> String -> !Bool -> !Bool -> !Bool -> !Bool -> !Bool -> !Bool -> !Bool -> !Bool -> !Bool -> !Bool -> !Bool -> !Bool -> !Bool -> IOSArrow XmlTree XmlTree -> !Bool -> IOSArrow XmlTree XmlTree -> XIOParseConfig [xioMimeTypes] :: XIOParseConfig -> MimeTypeTable [xioMimeTypeHandlers] :: XIOParseConfig -> MimeTypeHandlers [xioMimeTypeFile] :: XIOParseConfig -> String [xioAcceptedMimeTypes] :: XIOParseConfig -> [String] [xioFileMimeType] :: XIOParseConfig -> String [xioWarnings] :: XIOParseConfig -> !Bool [xioRemoveWS] :: XIOParseConfig -> !Bool [xioParseByMimeType] :: XIOParseConfig -> !Bool [xioParseHTML] :: XIOParseConfig -> !Bool [xioLowerCaseNames] :: XIOParseConfig -> !Bool [xioPreserveComment] :: XIOParseConfig -> !Bool [xioValidate] :: XIOParseConfig -> !Bool [xioSubstDTDEntities] :: XIOParseConfig -> !Bool [xioSubstHTMLEntities] :: XIOParseConfig -> !Bool [xioCheckNamespaces] :: XIOParseConfig -> !Bool [xioCanonicalize] :: XIOParseConfig -> !Bool [xioIgnoreNoneXmlContents] :: XIOParseConfig -> !Bool [xioTagSoup] :: XIOParseConfig -> !Bool [xioTagSoupParser] :: XIOParseConfig -> IOSArrow XmlTree XmlTree [xioExpat] :: XIOParseConfig -> !Bool [xioExpatParser] :: XIOParseConfig -> IOSArrow XmlTree XmlTree data XIOOutputConfig XIOOcfg :: !Bool -> !String -> !XIOXoutConfig -> !Bool -> ![String] -> !Bool -> !Bool -> !Bool -> !Bool -> XIOOutputConfig [xioIndent] :: XIOOutputConfig -> !Bool [xioOutputEncoding] :: XIOOutputConfig -> !String [xioOutputFmt] :: XIOOutputConfig -> !XIOXoutConfig [xioXmlPi] :: XIOOutputConfig -> !Bool [xioNoEmptyElemFor] :: XIOOutputConfig -> ![String] [xioAddDefaultDTD] :: XIOOutputConfig -> !Bool [xioTextMode] :: XIOOutputConfig -> !Bool [xioShowTree] :: XIOOutputConfig -> !Bool [xioShowHaskell] :: XIOOutputConfig -> !Bool data XIOXoutConfig XMLoutput :: XIOXoutConfig XHTMLoutput :: XIOXoutConfig HTMLoutput :: XIOXoutConfig PLAINoutput :: XIOXoutConfig data XIORelaxConfig XIORxc :: !Bool -> String -> !Bool -> !Bool -> !Bool -> !Bool -> IOSArrow XmlTree XmlTree -> XIORelaxConfig [xioRelaxValidate] :: XIORelaxConfig -> !Bool [xioRelaxSchema] :: XIORelaxConfig -> String [xioRelaxCheckRestr] :: XIORelaxConfig -> !Bool [xioRelaxValidateExtRef] :: XIORelaxConfig -> !Bool [xioRelaxValidateInclude] :: XIORelaxConfig -> !Bool [xioRelaxCollectErrors] :: XIORelaxConfig -> !Bool [xioRelaxValidator] :: XIORelaxConfig -> IOSArrow XmlTree XmlTree data XIOXmlSchemaConfig XIOScc :: !Bool -> String -> IOSArrow XmlTree XmlTree -> XIOXmlSchemaConfig [xioXmlSchemaValidate] :: XIOXmlSchemaConfig -> !Bool [xioXmlSchemaSchema] :: XIOXmlSchemaConfig -> String [xioXmlSchemaValidator] :: XIOXmlSchemaConfig -> IOSArrow XmlTree XmlTree data XIOCacheConfig XIOCch :: CompressionFct -> DeCompressionFct -> !Bool -> !String -> !Int -> !Bool -> (String -> IOSArrow XmlTree XmlTree) -> !Bool -> XIOCacheConfig [xioBinaryCompression] :: XIOCacheConfig -> CompressionFct [xioBinaryDeCompression] :: XIOCacheConfig -> DeCompressionFct [xioWithCache] :: XIOCacheConfig -> !Bool [xioCacheDir] :: XIOCacheConfig -> !String [xioDocumentAge] :: XIOCacheConfig -> !Int [xioCache404Err] :: XIOCacheConfig -> !Bool [xioCacheRead] :: XIOCacheConfig -> String -> IOSArrow XmlTree XmlTree [xioStrictDeserialize] :: XIOCacheConfig -> !Bool type MimeTypeHandlers = Map String (IOSArrow XmlTree XmlTree) type CompressionFct = ByteString -> ByteString type DeCompressionFct = ByteString -> ByteString type SysConfig = XIOSysState -> XIOSysState type SysConfigList = [SysConfig] theSysState :: Selector (XIOState us) XIOSysState theUserState :: Selector (XIOState us) us theSysWriter :: Selector XIOSysState XIOSysWriter theErrorStatus :: Selector XIOSysState Int theErrorMsgList :: Selector XIOSysState XmlTrees theRelaxNoOfErrors :: Selector XIOSysState Int theRelaxDefineId :: Selector XIOSysState Int theRelaxAttrList :: Selector XIOSysState (AssocList String XmlTrees) theSysEnv :: Selector XIOSysState XIOSysEnv theInputConfig :: Selector XIOSysState XIOInputConfig theStrictInput :: Selector XIOSysState Bool theEncodingErrors :: Selector XIOSysState Bool theInputEncoding :: Selector XIOSysState String theHttpHandler :: Selector XIOSysState (IOSArrow XmlTree XmlTree) theInputOptions :: Selector XIOSysState Attributes theRedirect :: Selector XIOSysState Bool theProxy :: Selector XIOSysState String theOutputConfig :: Selector XIOSysState XIOOutputConfig theIndent :: Selector XIOSysState Bool theOutputEncoding :: Selector XIOSysState String theOutputFmt :: Selector XIOSysState XIOXoutConfig theXmlPi :: Selector XIOSysState Bool theNoEmptyElemFor :: Selector XIOSysState [String] theAddDefaultDTD :: Selector XIOSysState Bool theTextMode :: Selector XIOSysState Bool theShowTree :: Selector XIOSysState Bool theShowHaskell :: Selector XIOSysState Bool theRelaxConfig :: Selector XIOSysState XIORelaxConfig theRelaxValidate :: Selector XIOSysState Bool theRelaxSchema :: Selector XIOSysState String theRelaxCheckRestr :: Selector XIOSysState Bool theRelaxValidateExtRef :: Selector XIOSysState Bool theRelaxValidateInclude :: Selector XIOSysState Bool theRelaxCollectErrors :: Selector XIOSysState Bool theRelaxValidator :: Selector XIOSysState (IOSArrow XmlTree XmlTree) theXmlSchemaConfig :: Selector XIOSysState XIOXmlSchemaConfig theXmlSchemaValidate :: Selector XIOSysState Bool theXmlSchemaSchema :: Selector XIOSysState String theXmlSchemaValidator :: Selector XIOSysState (IOSArrow XmlTree XmlTree) theParseConfig :: Selector XIOSysState XIOParseConfig theErrorMsgHandler :: Selector XIOSysState (String -> IO ()) theErrorMsgCollect :: Selector XIOSysState Bool theBaseURI :: Selector XIOSysState String theDefaultBaseURI :: Selector XIOSysState String theTraceLevel :: Selector XIOSysState Int theTraceCmd :: Selector XIOSysState (Int -> String -> IO ()) theTrace :: Selector XIOSysState (Int, Int -> String -> IO ()) theAttrList :: Selector XIOSysState Attributes theMimeTypes :: Selector XIOSysState MimeTypeTable theMimeTypeHandlers :: Selector XIOSysState MimeTypeHandlers theMimeTypeFile :: Selector XIOSysState String theAcceptedMimeTypes :: Selector XIOSysState [String] theFileMimeType :: Selector XIOSysState String theWarnings :: Selector XIOSysState Bool theRemoveWS :: Selector XIOSysState Bool thePreserveComment :: Selector XIOSysState Bool theParseByMimeType :: Selector XIOSysState Bool theParseHTML :: Selector XIOSysState Bool theLowerCaseNames :: Selector XIOSysState Bool theValidate :: Selector XIOSysState Bool theSubstDTDEntities :: Selector XIOSysState Bool theSubstHTMLEntities :: Selector XIOSysState Bool theCheckNamespaces :: Selector XIOSysState Bool theCanonicalize :: Selector XIOSysState Bool theIgnoreNoneXmlContents :: Selector XIOSysState Bool theTagSoup :: Selector XIOSysState Bool theTagSoupParser :: Selector XIOSysState (IOSArrow XmlTree XmlTree) theExpat :: Selector XIOSysState Bool theExpatParser :: Selector XIOSysState (IOSArrow XmlTree XmlTree) theExpatErrors :: Selector XIOSysState (IOSArrow XmlTree XmlTree) theCacheConfig :: Selector XIOSysState XIOCacheConfig theBinaryCompression :: Selector XIOSysState (ByteString -> ByteString) theBinaryDeCompression :: Selector XIOSysState (ByteString -> ByteString) theWithCache :: Selector XIOSysState Bool theCacheDir :: Selector XIOSysState String theDocumentAge :: Selector XIOSysState Int theCache404Err :: Selector XIOSysState Bool theCacheRead :: Selector XIOSysState (String -> IOSArrow XmlTree XmlTree) theStrictDeserialize :: Selector XIOSysState Bool getSysVar :: Selector XIOSysState c -> IOStateArrow s b c setSysVar :: Selector XIOSysState c -> IOStateArrow s c c chgSysVar :: Selector XIOSysState c -> (b -> c -> c) -> IOStateArrow s b b configSysVar :: SysConfig -> IOStateArrow s c c configSysVars :: SysConfigList -> IOStateArrow s c c localSysVar :: Selector XIOSysState c -> IOStateArrow s a b -> IOStateArrow s a b localSysEnv :: IOStateArrow s a b -> IOStateArrow s a b incrSysVar :: Selector XIOSysState Int -> IOStateArrow s a Int -- | store a string in global state under a given attribute name setSysAttr :: String -> IOStateArrow s String String -- | remove an entry in global state, arrow input remains unchanged unsetSysAttr :: String -> IOStateArrow s b b -- | read an attribute value from global state getSysAttr :: String -> IOStateArrow s b String -- | read all attributes from global state getAllSysAttrs :: IOStateArrow s b Attributes setSysAttrString :: String -> String -> IOStateArrow s b b -- | store an int value in global state setSysAttrInt :: String -> Int -> IOStateArrow s b b -- | read an int value from global state -- --
--   getSysAttrInt 0 myIntAttr
--   
getSysAttrInt :: Int -> String -> IOStateArrow s b Int toInt :: Int -> String -> Int -- | A Selector is a pair of an access function and a modifying function -- for reading and updating parts of a composite type data Selector s a S :: (s -> a) -> (a -> s -> s) -> Selector s a [getS] :: Selector s a -> s -> a [setS] :: Selector s a -> a -> s -> s chgS :: Selector s a -> (a -> a) -> (s -> s) idS :: Selector s s (.&&&.) :: Selector s a -> Selector s b -> Selector s (a, b) infixr 3 .&&&. instance GHC.Classes.Eq Text.XML.HXT.Arrow.XmlState.TypeDefs.XIOXoutConfig instance Control.DeepSeq.NFData us => Control.DeepSeq.NFData (Text.XML.HXT.Arrow.XmlState.TypeDefs.XIOState us) instance Control.DeepSeq.NFData Text.XML.HXT.Arrow.XmlState.TypeDefs.XIOSysState -- | the basic state arrows for XML processing -- -- A state is needed for global processing options, like encoding -- options, document base URI, trace levels and error message handling -- -- The state is separated into a user defined state and a system state. -- The system state contains variables for error message handling, for -- tracing, for the document base for accessing XML documents with -- relative references, e.g. DTDs, and a global key value store. This -- assoc list has strings as keys and lists of XmlTrees as values. It is -- used to store arbitrary XML and text values, e.g. user defined global -- options. -- -- The user defined part of the store is in the default case empty, -- defined as (). It can be extended with an arbitray data type module Text.XML.HXT.Arrow.XmlState.ErrorHandling changeErrorStatus :: (Int -> Int -> Int) -> IOStateArrow s Int Int -- | reset global error variable clearErrStatus :: IOStateArrow s b b -- | set global error variable setErrStatus :: IOStateArrow s Int Int -- | read current global error status getErrStatus :: IOStateArrow s XmlTree Int -- | raise the global error status level to that of the input tree setErrMsgStatus :: IOStateArrow s XmlTree XmlTree -- | set the error message handler and the flag for collecting the errors setErrorMsgHandler :: Bool -> (String -> IO ()) -> IOStateArrow s b b -- | error message handler for output to stderr sysErrorMsg :: IOStateArrow s XmlTree XmlTree -- | the default error message handler: error output to stderr errorMsgStderr :: IOStateArrow s b b -- | error message handler for collecting errors errorMsgCollect :: IOStateArrow s b b -- | error message handler for output to stderr and collecting errorMsgStderrAndCollect :: IOStateArrow s b b -- | error message handler for ignoring errors errorMsgIgnore :: IOStateArrow s b b -- | if error messages are collected by the error handler for processing -- these messages by the calling application, this arrow reads the stored -- messages and clears the error message store getErrorMessages :: IOStateArrow s b XmlTree addToErrorMsgList :: IOStateArrow s XmlTree XmlTree -- | filter error messages from input trees and issue errors filterErrorMsg :: IOStateArrow s XmlTree XmlTree -- | generate a warnig message issueWarn :: String -> IOStateArrow s b b -- | generate an error message issueErr :: String -> IOStateArrow s b b -- | generate a fatal error message, e.g. document not found issueFatal :: String -> IOStateArrow s b b -- | Default exception handler: issue a fatal error message and fail. -- -- The parameter can be used to specify where the error occured issueExc :: String -> IOStateArrow s SomeException b -- | add the error level and the module where the error occured to the -- attributes of a document root node and remove the children when level -- is greater or equal to c_err. called by -- setDocumentStatusFromSystemState when the system state -- indicates an error setDocumentStatus :: Int -> String -> IOStateArrow s XmlTree XmlTree -- | check whether the error level attribute in the system state is set to -- error, in this case the children of the document root are removed and -- the module name where the error occured and the error level are added -- as attributes with setDocumentStatus else nothing is changed setDocumentStatusFromSystemState :: String -> IOStateArrow s XmlTree XmlTree -- | check whether tree is a document root and the status attribute has a -- value less than c_err documentStatusOk :: ArrowXml a => a XmlTree XmlTree errorOutputToStderr :: String -> IO () -- | the mime type configuration functions module Text.XML.HXT.Arrow.XmlState.MimeTypeTable -- | set the table mapping of file extensions to mime types in the system -- state -- -- Default table is defined in MimeTypeDefaults. This table is -- used when reading loacl files, (file: protocol) to determine the mime -- type setMimeTypeTable :: MimeTypeTable -> IOStateArrow s b b -- | set the table mapping of file extensions to mime types by an external -- config file -- -- The config file must follow the conventions of etcmime.types on -- a debian linux system, that means all empty lines and all lines -- starting with a # are ignored. The other lines must consist of a mime -- type followed by a possible empty list of extensions. The list of -- extenstions and mime types overwrites the default list in the system -- state of the IOStateArrow setMimeTypeTableFromFile :: FilePath -> IOStateArrow s b b -- | read the system mimetype table getMimeTypeTable :: IOStateArrow s b MimeTypeTable -- | system configuration and common options options module Text.XML.HXT.Arrow.XmlState.SystemConfig -- | withTrace level : system option, set the trace level, (0..4) withTrace :: Int -> SysConfig -- | withSysAttr key value : store an arbitrary key value pair in -- system state withSysAttr :: String -> String -> SysConfig -- | Specify the set of accepted mime types. -- -- All contents of documents for which the mime type is not found in this -- list are discarded. withAcceptedMimeTypes :: [String] -> SysConfig -- | Specify a content handler for documents of a given mime type withMimeTypeHandler :: String -> IOSArrow XmlTree XmlTree -> SysConfig -- | withMimeTypeFile filename : input option, set the mime type -- table for file: documents by given file. The format of this -- config file must be in the syntax of a debian linux "mime.types" -- config file withMimeTypeFile :: String -> SysConfig -- | Force a given mime type for all file contents. -- -- The mime type for file access will then not be computed by looking -- into a mime.types file withFileMimeType :: String -> SysConfig -- | withWarnings yes/no : system option, issue warnings during -- reading, HTML parsing and processing, default is yes withWarnings :: Bool -> SysConfig -- | withErrors yes/no : system option for suppressing error -- messages, default is no withErrors :: Bool -> SysConfig -- | withRemoveWS yes/no : read and write option, remove all -- whitespace, used for document indentation, default is no withRemoveWS :: Bool -> SysConfig -- | withPreserveComment yes/no : read option, preserve comments -- during canonicalization, default is no withPreserveComment :: Bool -> SysConfig -- | withParseByMimeType yes/no : read option, select the parser -- by the mime type of the document (pulled out of the HTTP header). -- -- When the mime type is set to "text/html" the configured HTML parser is -- taken, when it's set to "text/xml" or "text/xhtml" the configured XML -- parser is taken. If the mime type is something else, no further -- processing is performed, the contents is given back to the application -- in form of a single text node. If the default document encoding is set -- to isoLatin1, this even enables processing of arbitray binary data. withParseByMimeType :: Bool -> SysConfig -- | withParseHTML yes/no: read option, use HTML parser, default -- is no (use XML parser) withParseHTML :: Bool -> SysConfig -- | withValidate yes/no: read option, validate document against -- DTD, default is yes withValidate :: Bool -> SysConfig -- | withSubstDTDEntities yes/no: read option, substitute general -- entities defined in DTD, default is yes. switching this option -- and the validate option off can lead to faster parsing, because then -- there is no need to access the DTD withSubstDTDEntities :: Bool -> SysConfig -- | withSubstHTMLEntities yes/no: read option, substitute general -- entities defined in HTML DTD, default is no. switching this -- option on and the substDTDEntities and validate options off can lead -- to faster parsing because there is no need to access a DTD, but still -- the HTML general entities are substituted withSubstHTMLEntities :: Bool -> SysConfig -- | withCheckNamespaces yes/no: read option, check namespaces, -- default is no withCheckNamespaces :: Bool -> SysConfig -- | withCanonicalize yes/no : read option, canonicalize document, -- default is yes withCanonicalize :: Bool -> SysConfig -- | withIgnoreNoneXmlContents yes/no : input option, ignore -- document contents of none XML/HTML documents. -- -- This option can be useful for implementing crawler like applications, -- e.g. an URL checker. In those cases net traffic can be reduced. withIgnoreNoneXmlContents :: Bool -> SysConfig -- | withStrictInput yes/no : input option, input of file and HTTP -- contents is read eagerly, default is no withStrictInput :: Bool -> SysConfig -- | withEncodingErrors yes/no : input option, ignore all encoding -- errors, default is no withEncodingErrors :: Bool -> SysConfig -- | withInputEncoding encodingName : input option -- -- Set default document encoding (utf8, isoLatin1, -- usAscii, iso8859_2, ... , iso8859_16, ...). Only -- XML, HTML and text documents are decoded, default decoding for -- XML/HTML is utf8, for text iso latin1 (no decoding). withInputEncoding :: String -> SysConfig -- | withDefaultBaseURI URI , input option, set the default base -- URI -- -- This option can be useful when parsing documents from stdin or -- contained in a string, and interpreting relative URIs within the -- document withDefaultBaseURI :: String -> SysConfig withInputOption :: String -> String -> SysConfig withInputOptions :: Attributes -> SysConfig -- | withRedirect yes/no : input option, automatically follow -- redirected URIs, default is yes withRedirect :: Bool -> SysConfig -- | withProxy "host:port" : input option, configure a proxy for -- HTTP access, e.g. www-cache:3128 withProxy :: String -> SysConfig -- | withIndent yes/no : output option, indent document before -- output, default is no withIndent :: Bool -> SysConfig -- | withOutputEncoding encoding , output option, default is the -- default input encoding or utf8, if input encoding is not set withOutputEncoding :: String -> SysConfig -- | withOutputXML : output option, default writing -- -- Default is writing XML: quote special XML chars >,<,",',& -- where neccessary, add XML processing instruction and encode document -- with respect to withOutputEncoding withOutputXML :: SysConfig -- | Write XHTML: quote all special XML chars, use HTML entity refs or char -- refs for none ASCII chars withOutputHTML :: SysConfig -- | Write XML: quote only special XML chars, don't substitute chars by -- HTML entities, and don't generate empty elements for HTML elements, -- which may contain any contents, e.g. -- src=.../script instead of src=... -- / withOutputXHTML :: SysConfig -- | suppreses all char and entitiy substitution withOutputPLAIN :: SysConfig withXmlPi :: Bool -> SysConfig withNoEmptyElemFor :: [String] -> SysConfig withAddDefaultDTD :: Bool -> SysConfig withTextMode :: Bool -> SysConfig withShowTree :: Bool -> SysConfig withShowHaskell :: Bool -> SysConfig -- | Configure compression and decompression for binary -- serialization/deserialization. First component is the compression -- function applied after serialization, second the decompression applied -- before deserialization. withCompression :: (CompressionFct, DeCompressionFct) -> SysConfig -- | Strict input for deserialization of binary data withStrictDeserialize :: Bool -> SysConfig yes :: Bool no :: Bool -- | system configuration and common options options module Text.XML.HXT.Arrow.XmlOptions -- | commonly useful options for XML input -- -- can be used for option definition with haskell getopt -- -- defines options: a_trace, a_proxy, a_use_curl, -- a_do_not_use_curl, a_options_curl, -- a_encoding, a_issue_errors, -- a_do_not_issue_errors, a_parse_html, -- a_parse_by_mimetype, a_issue_warnings, -- a_do_not_issue_warnings, a_parse_xml, a_validate, -- a_do_not_validate, a_canonicalize, -- a_do_not_canonicalize, inputOptions :: [OptDescr SysConfig] -- | commonly useful options for XML output -- -- defines options: a_indent, a_output_encoding, -- a_output_html and others outputOptions :: [OptDescr SysConfig] -- | commonly useful options -- -- defines options: a_verbose, a_help generalOptions :: [OptDescr SysConfig] -- | defines a_version option versionOptions :: [OptDescr SysConfig] -- | debug output options showOptions :: [OptDescr SysConfig] a_accept_mimetypes :: String a_add_default_dtd :: String a_canonicalize :: String a_check_namespaces :: String a_collect_errors :: String a_default_baseuri :: String a_do_not_canonicalize :: String a_do_not_check_namespaces :: String a_do_not_issue_errors :: String a_do_not_issue_warnings :: String a_do_not_preserve_comment :: String a_do_not_remove_whitespace :: String a_do_not_subst_dtd_entities :: String a_do_not_subst_html_entities :: String a_do_not_validate :: String a_error :: String a_error_log :: String a_help :: String a_if_modified_since :: String a_if_unmodified_since :: String a_ignore_encoding_errors :: String a_ignore_none_xml_contents :: String a_indent :: String a_issue_errors :: String a_issue_warnings :: String a_mime_types :: String a_no_empty_elements :: String a_no_empty_elem_for :: String a_no_redirect :: String a_no_xml_pi :: String a_output_file :: String a_output_xml :: String a_output_html :: String a_output_xhtml :: String a_output_plain :: String a_parse_by_mimetype :: String a_parse_html :: String a_parse_xml :: String a_preserve_comment :: String a_proxy :: String a_redirect :: String a_remove_whitespace :: String a_show_haskell :: String a_show_tree :: String a_strict_input :: String a_subst_dtd_entities :: String a_subst_html_entities :: String a_text_mode :: String a_trace :: String a_validate :: String a_verbose :: String -- | select options from a predefined list of option descriptions selectOptions :: [String] -> [OptDescr a] -> [OptDescr a] removeOptions :: [String] -> [OptDescr a] -> [OptDescr a] -- | the trace arrows module Text.XML.HXT.Arrow.XmlState.TraceHandling -- | set the global trace level setTraceLevel :: Int -> IOStateArrow s b b -- | read the global trace level getTraceLevel :: IOStateArrow s b Int -- | set the global trace command. This command does the trace output setTraceCmd :: (Int -> String -> IO ()) -> IOStateArrow s b b -- | acces the command for trace output getTraceCmd :: IOStateArrow a b (Int -> String -> IO ()) -- | run an arrow with a given trace level, the old trace level is restored -- after the arrow execution withTraceLevel :: Int -> IOStateArrow s b c -> IOStateArrow s b c -- | apply a trace arrow and issue message to stderr trace :: Int -> IOStateArrow s b String -> IOStateArrow s b b -- | trace the current value transfered in a sequence of arrows. -- -- The value is formated by a string conversion function. This is a -- substitute for the old and less general traceString function traceValue :: Int -> (b -> String) -> IOStateArrow s b b -- | an old alias for traceValue traceString :: Int -> (b -> String) -> IOStateArrow s b b -- | issue a string message as trace traceMsg :: Int -> String -> IOStateArrow s b b -- | issue the source representation of a document if trace level >= 3 -- -- for better readability the source is formated with indentDoc traceSource :: IOStateArrow s XmlTree XmlTree -- | issue the tree representation of a document if trace level >= 4 traceTree :: IOStateArrow s XmlTree XmlTree -- | trace a main computation step issue a message when trace level >= -- 1, issue document source if level >= 3, issue tree when level is -- >= 4 traceDoc :: String -> IOStateArrow s XmlTree XmlTree traceOutputToStderr :: Int -> String -> IO () -- | run an io state arrow module Text.XML.HXT.Arrow.XmlState.RunIOStateArrow -- | apply an IOSArrow to an empty root node with -- initialState () as initial state -- -- the main entry point for running a state arrow with IO -- -- when running runX f an empty XML root node is applied to -- f. usually f will start with a constant arrow -- (ignoring the input), e.g. a readDocument arrow. -- -- for usage see examples with writeDocument -- -- if input has to be feed into the arrow use runIOSLA like in -- runIOSLA f emptyX inputDoc runX :: IOSArrow XmlTree c -> IO [c] runXIOState :: XIOState s -> IOStateArrow s XmlTree c -> IO [c] -- | the default global state, used as initial state when running an -- IOSArrow with runIOSLA or runX initialState :: us -> XIOState us initialSysState :: XIOSysState initialSysWriter :: XIOSysWriter initialSysEnv :: XIOSysEnv initialInputConfig :: XIOInputConfig initialParseConfig :: XIOParseConfig initialOutputConfig :: XIOOutputConfig initialRelaxConfig :: XIORelaxConfig initialXmlSchemaConfig :: XIOXmlSchemaConfig initialCacheConfig :: XIOCacheConfig dummyHTTPHandler :: IOSArrow XmlTree XmlTree dummyTagSoupParser :: IOSArrow b b dummyExpatParser :: IOSArrow b b dummyRelaxValidator :: IOSArrow b b dummyXmlSchemaValidator :: IOSArrow b b dummyCacheRead :: String -> IOSArrow b b getConfigAttr :: String -> SysConfigList -> String theSysConfigComp :: Selector XIOSysState a -> Selector SysConfig a -- | the basic state arrows for URI handling module Text.XML.HXT.Arrow.XmlState.URIHandling -- | set the base URI of a document, used e.g. for reading includes, e.g. -- external entities, the input must be an absolute URI setBaseURI :: IOStateArrow s String String -- | read the base URI from the globale state getBaseURI :: IOStateArrow s b String -- | change the base URI with a possibly relative URI, can be used for -- evaluating the xml:base attribute. Returns the new absolute base URI. -- Fails, if input is not parsable with parseURIReference -- -- see also: setBaseURI, mkAbsURI changeBaseURI :: IOStateArrow s String String -- | set the default base URI, if parameter is null, the system base ( -- file:///<cwd>/ ) is used, else the parameter, must be -- called before any document is read setDefaultBaseURI :: String -> IOStateArrow s b String -- | get the default base URI getDefaultBaseURI :: IOStateArrow s b String -- | remember base uri, run an arrow and restore the base URI, used with -- external entity substitution runInLocalURIContext :: IOStateArrow s b c -> IOStateArrow s b c -- | parse a URI reference, in case of a failure, try to escape unescaped -- chars, convert backslashes to slashes for windows paths, and try -- parsing again parseURIReference' :: String -> Maybe URI -- | compute the absolut URI for a given URI and a base URI expandURIString :: String -> String -> Maybe String -- | arrow variant of expandURIString, fails if -- expandURIString returns Nothing expandURI :: ArrowXml a => a (String, String) String -- | arrow for expanding an input URI into an absolute URI using global -- base URI, fails if input is not a legal URI mkAbsURI :: IOStateArrow s String String -- | arrow for selecting the scheme (protocol) of the URI, fails if input -- is not a legal URI. -- -- See Network.URI for URI components getSchemeFromURI :: ArrowList a => a String String -- | arrow for selecting the registered name (host) of the URI, fails if -- input is not a legal URI getRegNameFromURI :: ArrowList a => a String String -- | arrow for selecting the port number of the URI without leading ':', -- fails if input is not a legal URI getPortFromURI :: ArrowList a => a String String -- | arrow for selecting the user info of the URI without trailing '@', -- fails if input is not a legal URI getUserInfoFromURI :: ArrowList a => a String String -- | arrow for computing the path component of an URI, fails if input is -- not a legal URI getPathFromURI :: ArrowList a => a String String -- | arrow for computing the query component of an URI, fails if input is -- not a legal URI getQueryFromURI :: ArrowList a => a String String -- | arrow for computing the fragment component of an URI, fails if input -- is not a legal URI getFragmentFromURI :: ArrowList a => a String String -- | arrow for computing the path component of an URI, fails if input is -- not a legal URI getPartFromURI :: ArrowList a => (URI -> String) -> a String String -- | the interface for the basic state maipulation functions module Text.XML.HXT.Arrow.XmlState -- | state datatype consists of a system state and a user state the user -- state is not fixed data XIOState us -- | predefined system state data type with all components for the system -- functions, like trace, error handling, ... data XIOSysState -- | The arrow type for stateful arrows type IOStateArrow s b c = IOSLA (XIOState s) b c -- | The arrow for stateful arrows with no user defined state type IOSArrow b c = IOStateArrow () b c type SysConfig = XIOSysState -> XIOSysState type SysConfigList = [SysConfig] -- | read the user defined part of the state getUserState :: IOStateArrow s b s -- | set the user defined part of the state setUserState :: IOStateArrow s s s -- | change the user defined part of the state changeUserState :: (b -> s -> s) -> IOStateArrow s b b -- | extend user state -- -- Run an arrow with an extended user state component, The old component -- is stored together with a new one in a pair, the arrow is executed -- with this extended state, and the augmented state component is removed -- form the state when the arrow has finished its execution withExtendedUserState :: s1 -> IOStateArrow (s1, s0) b c -> IOStateArrow s0 b c -- | change the type of user state -- -- This conversion is useful, when running a state arrow with another -- structure of the user state, e.g. with () when executing some IO -- arrows withOtherUserState :: s1 -> IOStateArrow s1 b c -> IOStateArrow s0 b c withoutUserState :: IOSArrow b c -> IOStateArrow s0 b c -- | apply an IOSArrow to an empty root node with -- initialState () as initial state -- -- the main entry point for running a state arrow with IO -- -- when running runX f an empty XML root node is applied to -- f. usually f will start with a constant arrow -- (ignoring the input), e.g. a readDocument arrow. -- -- for usage see examples with writeDocument -- -- if input has to be feed into the arrow use runIOSLA like in -- runIOSLA f emptyX inputDoc runX :: IOSArrow XmlTree c -> IO [c] configSysVars :: SysConfigList -> IOStateArrow s c c -- | store a string in global state under a given attribute name setSysAttr :: String -> IOStateArrow s String String -- | remove an entry in global state, arrow input remains unchanged unsetSysAttr :: String -> IOStateArrow s b b -- | read an attribute value from global state getSysAttr :: String -> IOStateArrow s b String -- | read all attributes from global state getAllSysAttrs :: IOStateArrow s b Attributes setSysAttrString :: String -> String -> IOStateArrow s b b -- | store an int value in global state setSysAttrInt :: String -> Int -> IOStateArrow s b b -- | read an int value from global state -- --
--   getSysAttrInt 0 myIntAttr
--   
getSysAttrInt :: Int -> String -> IOStateArrow s b Int getConfigAttr :: String -> SysConfigList -> String -- | reset global error variable clearErrStatus :: IOStateArrow s b b -- | set global error variable setErrStatus :: IOStateArrow s Int Int -- | read current global error status getErrStatus :: IOStateArrow s XmlTree Int -- | raise the global error status level to that of the input tree setErrMsgStatus :: IOStateArrow s XmlTree XmlTree -- | set the error message handler and the flag for collecting the errors setErrorMsgHandler :: Bool -> (String -> IO ()) -> IOStateArrow s b b -- | the default error message handler: error output to stderr errorMsgStderr :: IOStateArrow s b b -- | error message handler for collecting errors errorMsgCollect :: IOStateArrow s b b -- | error message handler for output to stderr and collecting errorMsgStderrAndCollect :: IOStateArrow s b b -- | error message handler for ignoring errors errorMsgIgnore :: IOStateArrow s b b -- | if error messages are collected by the error handler for processing -- these messages by the calling application, this arrow reads the stored -- messages and clears the error message store getErrorMessages :: IOStateArrow s b XmlTree -- | filter error messages from input trees and issue errors filterErrorMsg :: IOStateArrow s XmlTree XmlTree -- | generate a warnig message issueWarn :: String -> IOStateArrow s b b -- | generate an error message issueErr :: String -> IOStateArrow s b b -- | generate a fatal error message, e.g. document not found issueFatal :: String -> IOStateArrow s b b -- | Default exception handler: issue a fatal error message and fail. -- -- The parameter can be used to specify where the error occured issueExc :: String -> IOStateArrow s SomeException b -- | add the error level and the module where the error occured to the -- attributes of a document root node and remove the children when level -- is greater or equal to c_err. called by -- setDocumentStatusFromSystemState when the system state -- indicates an error setDocumentStatus :: Int -> String -> IOStateArrow s XmlTree XmlTree -- | check whether the error level attribute in the system state is set to -- error, in this case the children of the document root are removed and -- the module name where the error occured and the error level are added -- as attributes with setDocumentStatus else nothing is changed setDocumentStatusFromSystemState :: String -> IOStateArrow s XmlTree XmlTree -- | check whether tree is a document root and the status attribute has a -- value less than c_err documentStatusOk :: ArrowXml a => a XmlTree XmlTree -- | set the global trace level setTraceLevel :: Int -> IOStateArrow s b b -- | read the global trace level getTraceLevel :: IOStateArrow s b Int -- | run an arrow with a given trace level, the old trace level is restored -- after the arrow execution withTraceLevel :: Int -> IOStateArrow s b c -> IOStateArrow s b c -- | set the global trace command. This command does the trace output setTraceCmd :: (Int -> String -> IO ()) -> IOStateArrow s b b -- | acces the command for trace output getTraceCmd :: IOStateArrow a b (Int -> String -> IO ()) -- | apply a trace arrow and issue message to stderr trace :: Int -> IOStateArrow s b String -> IOStateArrow s b b -- | issue a string message as trace traceMsg :: Int -> String -> IOStateArrow s b b -- | trace the current value transfered in a sequence of arrows. -- -- The value is formated by a string conversion function. This is a -- substitute for the old and less general traceString function traceValue :: Int -> (b -> String) -> IOStateArrow s b b -- | an old alias for traceValue traceString :: Int -> (b -> String) -> IOStateArrow s b b -- | issue the source representation of a document if trace level >= 3 -- -- for better readability the source is formated with indentDoc traceSource :: IOStateArrow s XmlTree XmlTree -- | issue the tree representation of a document if trace level >= 4 traceTree :: IOStateArrow s XmlTree XmlTree -- | trace a main computation step issue a message when trace level >= -- 1, issue document source if level >= 3, issue tree when level is -- >= 4 traceDoc :: String -> IOStateArrow s XmlTree XmlTree -- | set the base URI of a document, used e.g. for reading includes, e.g. -- external entities, the input must be an absolute URI setBaseURI :: IOStateArrow s String String -- | read the base URI from the globale state getBaseURI :: IOStateArrow s b String -- | change the base URI with a possibly relative URI, can be used for -- evaluating the xml:base attribute. Returns the new absolute base URI. -- Fails, if input is not parsable with parseURIReference -- -- see also: setBaseURI, mkAbsURI changeBaseURI :: IOStateArrow s String String -- | set the default base URI, if parameter is null, the system base ( -- file:///<cwd>/ ) is used, else the parameter, must be -- called before any document is read setDefaultBaseURI :: String -> IOStateArrow s b String -- | get the default base URI getDefaultBaseURI :: IOStateArrow s b String -- | remember base uri, run an arrow and restore the base URI, used with -- external entity substitution runInLocalURIContext :: IOStateArrow s b c -> IOStateArrow s b c -- | compute the absolut URI for a given URI and a base URI expandURIString :: String -> String -> Maybe String -- | arrow variant of expandURIString, fails if -- expandURIString returns Nothing expandURI :: ArrowXml a => a (String, String) String -- | arrow for expanding an input URI into an absolute URI using global -- base URI, fails if input is not a legal URI mkAbsURI :: IOStateArrow s String String -- | arrow for computing the fragment component of an URI, fails if input -- is not a legal URI getFragmentFromURI :: ArrowList a => a String String -- | arrow for computing the path component of an URI, fails if input is -- not a legal URI getPathFromURI :: ArrowList a => a String String -- | arrow for selecting the port number of the URI without leading ':', -- fails if input is not a legal URI getPortFromURI :: ArrowList a => a String String -- | arrow for computing the query component of an URI, fails if input is -- not a legal URI getQueryFromURI :: ArrowList a => a String String -- | arrow for selecting the registered name (host) of the URI, fails if -- input is not a legal URI getRegNameFromURI :: ArrowList a => a String String -- | arrow for selecting the scheme (protocol) of the URI, fails if input -- is not a legal URI. -- -- See Network.URI for URI components getSchemeFromURI :: ArrowList a => a String String -- | arrow for selecting the user info of the URI without trailing '@', -- fails if input is not a legal URI getUserInfoFromURI :: ArrowList a => a String String -- | read the system mimetype table getMimeTypeTable :: IOStateArrow s b MimeTypeTable -- | set the table mapping of file extensions to mime types in the system -- state -- -- Default table is defined in MimeTypeDefaults. This table is -- used when reading loacl files, (file: protocol) to determine the mime -- type setMimeTypeTable :: MimeTypeTable -> IOStateArrow s b b -- | set the table mapping of file extensions to mime types by an external -- config file -- -- The config file must follow the conventions of etcmime.types on -- a debian linux system, that means all empty lines and all lines -- starting with a # are ignored. The other lines must consist of a mime -- type followed by a possible empty list of extensions. The list of -- extenstions and mime types overwrites the default list in the system -- state of the IOStateArrow setMimeTypeTableFromFile :: FilePath -> IOStateArrow s b b yes :: Bool no :: Bool -- | Specify the set of accepted mime types. -- -- All contents of documents for which the mime type is not found in this -- list are discarded. withAcceptedMimeTypes :: [String] -> SysConfig withAddDefaultDTD :: Bool -> SysConfig -- | withSysAttr key value : store an arbitrary key value pair in -- system state withSysAttr :: String -> String -> SysConfig -- | withCanonicalize yes/no : read option, canonicalize document, -- default is yes withCanonicalize :: Bool -> SysConfig -- | Configure compression and decompression for binary -- serialization/deserialization. First component is the compression -- function applied after serialization, second the decompression applied -- before deserialization. withCompression :: (CompressionFct, DeCompressionFct) -> SysConfig -- | withCheckNamespaces yes/no: read option, check namespaces, -- default is no withCheckNamespaces :: Bool -> SysConfig -- | withDefaultBaseURI URI , input option, set the default base -- URI -- -- This option can be useful when parsing documents from stdin or -- contained in a string, and interpreting relative URIs within the -- document withDefaultBaseURI :: String -> SysConfig -- | Strict input for deserialization of binary data withStrictDeserialize :: Bool -> SysConfig -- | withEncodingErrors yes/no : input option, ignore all encoding -- errors, default is no withEncodingErrors :: Bool -> SysConfig -- | withErrors yes/no : system option for suppressing error -- messages, default is no withErrors :: Bool -> SysConfig -- | Force a given mime type for all file contents. -- -- The mime type for file access will then not be computed by looking -- into a mime.types file withFileMimeType :: String -> SysConfig -- | withIgnoreNoneXmlContents yes/no : input option, ignore -- document contents of none XML/HTML documents. -- -- This option can be useful for implementing crawler like applications, -- e.g. an URL checker. In those cases net traffic can be reduced. withIgnoreNoneXmlContents :: Bool -> SysConfig -- | withIndent yes/no : output option, indent document before -- output, default is no withIndent :: Bool -> SysConfig -- | withInputEncoding encodingName : input option -- -- Set default document encoding (utf8, isoLatin1, -- usAscii, iso8859_2, ... , iso8859_16, ...). Only -- XML, HTML and text documents are decoded, default decoding for -- XML/HTML is utf8, for text iso latin1 (no decoding). withInputEncoding :: String -> SysConfig withInputOption :: String -> String -> SysConfig withInputOptions :: Attributes -> SysConfig -- | withMimeTypeFile filename : input option, set the mime type -- table for file: documents by given file. The format of this -- config file must be in the syntax of a debian linux "mime.types" -- config file withMimeTypeFile :: String -> SysConfig -- | Specify a content handler for documents of a given mime type withMimeTypeHandler :: String -> IOSArrow XmlTree XmlTree -> SysConfig withNoEmptyElemFor :: [String] -> SysConfig withXmlPi :: Bool -> SysConfig -- | withOutputEncoding encoding , output option, default is the -- default input encoding or utf8, if input encoding is not set withOutputEncoding :: String -> SysConfig -- | withOutputXML : output option, default writing -- -- Default is writing XML: quote special XML chars >,<,",',& -- where neccessary, add XML processing instruction and encode document -- with respect to withOutputEncoding withOutputXML :: SysConfig -- | Write XHTML: quote all special XML chars, use HTML entity refs or char -- refs for none ASCII chars withOutputHTML :: SysConfig -- | Write XML: quote only special XML chars, don't substitute chars by -- HTML entities, and don't generate empty elements for HTML elements, -- which may contain any contents, e.g. -- src=.../script instead of src=... -- / withOutputXHTML :: SysConfig -- | suppreses all char and entitiy substitution withOutputPLAIN :: SysConfig -- | withParseByMimeType yes/no : read option, select the parser -- by the mime type of the document (pulled out of the HTTP header). -- -- When the mime type is set to "text/html" the configured HTML parser is -- taken, when it's set to "text/xml" or "text/xhtml" the configured XML -- parser is taken. If the mime type is something else, no further -- processing is performed, the contents is given back to the application -- in form of a single text node. If the default document encoding is set -- to isoLatin1, this even enables processing of arbitray binary data. withParseByMimeType :: Bool -> SysConfig -- | withParseHTML yes/no: read option, use HTML parser, default -- is no (use XML parser) withParseHTML :: Bool -> SysConfig -- | withPreserveComment yes/no : read option, preserve comments -- during canonicalization, default is no withPreserveComment :: Bool -> SysConfig -- | withProxy "host:port" : input option, configure a proxy for -- HTTP access, e.g. www-cache:3128 withProxy :: String -> SysConfig -- | withRedirect yes/no : input option, automatically follow -- redirected URIs, default is yes withRedirect :: Bool -> SysConfig -- | withRemoveWS yes/no : read and write option, remove all -- whitespace, used for document indentation, default is no withRemoveWS :: Bool -> SysConfig withShowHaskell :: Bool -> SysConfig withShowTree :: Bool -> SysConfig -- | withStrictInput yes/no : input option, input of file and HTTP -- contents is read eagerly, default is no withStrictInput :: Bool -> SysConfig -- | withSubstDTDEntities yes/no: read option, substitute general -- entities defined in DTD, default is yes. switching this option -- and the validate option off can lead to faster parsing, because then -- there is no need to access the DTD withSubstDTDEntities :: Bool -> SysConfig -- | withSubstHTMLEntities yes/no: read option, substitute general -- entities defined in HTML DTD, default is no. switching this -- option on and the substDTDEntities and validate options off can lead -- to faster parsing because there is no need to access a DTD, but still -- the HTML general entities are substituted withSubstHTMLEntities :: Bool -> SysConfig withTextMode :: Bool -> SysConfig -- | withTrace level : system option, set the trace level, (0..4) withTrace :: Int -> SysConfig -- | withValidate yes/no: read option, validate document against -- DTD, default is yes withValidate :: Bool -> SysConfig -- | withWarnings yes/no : system option, issue warnings during -- reading, HTML parsing and processing, default is yes withWarnings :: Bool -> SysConfig -- | State arrows for document input module Text.XML.HXT.Arrow.DocumentInput -- | Read the content of a document. -- -- This routine is usually called from getDocumentContents. -- -- The input must be a root node (constructed with root), usually -- without children. The attribute list contains all input parameters, -- e.g. URI or source file name, encoding preferences, ... If the source -- name is empty, the input is read from standard input. -- -- The source is transformed into an absolute URI. If the source is a -- relative URI, or a file name, it is expanded into an absolute URI with -- respect to the current base URI. The default base URI is of protocol -- "file" and points to the current working directory. -- -- The currently supported protocols are "http", "file", "stdin" and -- "string". -- -- The latter two are internal protocols. An uri of the form "stdin:" -- stands for the content of the standard input stream. -- -- "string:some text" means, that "some text" is taken as input. This -- internal protocol is used for reading from normal String -- values. getXmlContents :: IOStateArrow s XmlTree XmlTree getXmlEntityContents :: IOStateArrow s XmlTree XmlTree getEncoding :: IOStateArrow s XmlTree String getTextEncoding :: IOStateArrow s XmlTree String decodeDocument :: IOStateArrow s XmlTree XmlTree addInputError :: Attributes -> String -> IOStateArrow s XmlTree XmlTree -- | DTD processing function for including external parts of a DTD -- parameter entity substitution and general entity substitution -- -- Implemtation completely done with arrows module Text.XML.HXT.Arrow.DTDProcessing -- | a filter for DTD processing -- -- inclusion of external parts of DTD, parameter entity substitution -- conditional section evaluation -- -- input tree must represent a complete document including root node processDTD :: IOStateArrow s XmlTree XmlTree instance GHC.Classes.Eq Text.XML.HXT.Arrow.DTDProcessing.DTDPart -- | general entity substitution module Text.XML.HXT.Arrow.GeneralEntitySubstitution -- | substitution of general entities -- -- input: a complete document tree including root node processGeneralEntities :: IOStateArrow s XmlTree XmlTree -- | Compound arrows for reading, parsing, validating and writing XML -- documents -- -- All arrows use IO and a global state for options, errorhandling, ... module Text.XML.HXT.Arrow.ProcessDocument -- | XML parser -- -- Input tree must be a root tree with a text tree as child containing -- the document to be parsed. The parser generates from the input string -- a tree of a wellformed XML document, processes the DTD (parameter -- substitution, conditional DTD parts, ...) and substitutes all general -- entity references. Next step is character reference substitution. Last -- step is the document validation. Validation can be controlled by an -- extra parameter. -- -- Example: -- --
--   parseXmlDocument True    -- parse and validate document
--   
--   parseXmlDocument False   -- only parse document, don't validate
--   
-- -- This parser is useful for applications processing correct XML -- documents. parseXmlDocument :: Bool -> Bool -> Bool -> Bool -> IOStateArrow s XmlTree XmlTree parseXmlDocumentWithExpat :: IOStateArrow s XmlTree XmlTree -- | HTML parser -- -- Input tree must be a root tree with a text tree as child containing -- the document to be parsed. The parser tries to parse everything as -- HTML, if the HTML document is not wellformed XML or if errors occur, -- warnings are generated. The warnings can be issued, or suppressed. -- -- Example: parseHtmlDocument True : parse document and issue -- warnings -- -- This parser is useful for applications like web crawlers, where the -- pages may contain arbitray errors, but the application is only -- interested in parts of the document, e.g. the plain text. parseHtmlDocument :: IOStateArrow s XmlTree XmlTree -- | Document validation -- -- Input must be a complete document tree. The document is validated with -- respect to the DTD spec. Only useful for XML documents containing a -- DTD. -- -- If the document is valid, it is transformed with respect to the DTD, -- normalization of attribute values, adding default values, sorting -- attributes by name,... -- -- If no error was found, result is the normalized tree, else the error -- status is set in the list of attributes of the root node "/" and the -- document content is removed from the tree. validateDocument :: IOStateArrow s XmlTree XmlTree -- | Namespace propagation -- -- Input must be a complete document tree. The namespace declarations are -- evaluated and all element and attribute names are processed by -- splitting the name into prefix, local part and namespace URI. -- -- Naames are checked with respect to the XML namespace definition -- -- If no error was found, result is the unchanged input tree, else the -- error status is set in the list of attributes of the root node "/" and -- the document content is removed from the tree. propagateAndValidateNamespaces :: IOStateArrow s XmlTree XmlTree andValidateNamespaces :: IOStateArrow s XmlTree XmlTree -- | creates a new document root, adds all options as attributes to the -- document root and calls getXmlContents. -- -- If the document name is the empty string, the document will be read -- from standard input. -- -- For supported protocols see getXmlContents getDocumentContents :: String -> IOStateArrow s b XmlTree -- | Module for importing all list arrows module Control.Arrow.ListArrows -- | Compound arrows for reading an XML/HTML document or an XML/HTML string module Text.XML.HXT.Arrow.ReadDocument -- | the main document input filter -- -- this filter can be configured by a list of configuration options, a -- value of type SysConfig -- -- for all available options see module SystemConfig -- -- -- -- examples: -- --
--   readDocument [] "test.xml"
--   
-- -- reads and validates a document "test.xml", no namespace propagation, -- only canonicalization is performed -- --
--   ...
--   import Text.XML.HXT.Curl
--   ...
--   
--   readDocument [ withValidate        no
--                , withInputEncoding   isoLatin1
--                , withParseByMimeType yes
--                , withCurl []
--                ] "http://localhost/test.php"
--   
-- -- reads document "test.php", parses it as HTML or XML depending on the -- mimetype given from the server, but without validation, default -- encoding isoLatin1. HTTP access is done via libCurl. -- --
--   readDocument [ withParseHTML       yes
--                , withInputEncoding   isoLatin1
--                ] ""
--   
-- -- reads a HTML document from standard input, no validation is done when -- parsing HTML, default encoding is isoLatin1, -- --
--   readDocument [ withInputEncoding  isoLatin1
--                , withValidate       no
--                , withMimeTypeFile   "/etc/mime.types"
--                , withStrictInput    yes
--                ] "test.svg"
--   
-- -- reads an SVG document from "test.svg", sets the mime type by looking -- in the system mimetype config file, default encoding is -- isoLatin1, -- --
--   ...
--   import Text.XML.HXT.Curl
--   import Text.XML.HXT.TagSoup
--   ...
--   
--   readDocument [ withParseHTML      yes
--                , withTagSoup
--                , withProxy          "www-cache:3128"
--                , withCurl           []
--                , withWarnings       no
--                ] "http://www.haskell.org/"
--   
-- -- reads Haskell homepage with HTML parser, ignoring any warnings (at the -- time of writing, there were some HTML errors), with http access via -- libCurl interface and proxy "www-cache" at port 3128, parsing is done -- with tagsoup HTML parser. This requires packages "hxt-curl" and -- "hxt-tagsoup" to be installed -- --
--   readDocument [ withValidate          yes
--                , withCheckNamespaces   yes
--                , withRemoveWS          yes
--                , withTrace             2
--                , withHTTP              []
--                ] "http://www.w3c.org/"
--   
-- -- read w3c home page (xhtml), validate and check namespaces, remove -- whitespace between tags, trace activities with level 2. HTTP access is -- done with Haskell HTTP package -- --
--   readDocument [ withValidate          no
--                , withSubstDTDEntities  no
--                ...
--                ] "http://www.w3c.org/"
--   
-- -- read w3c home page (xhtml), but without accessing the DTD given in -- that document. Only the predefined XML general entity refs are -- substituted. -- --
--   readDocument [ withValidate          no
--                , withSubstDTDEntities  no
--                , withSubstHTMLEntities yes
--                ...
--                ] "http://www.w3c.org/"
--   
-- -- same as above, but with substituion of all general entity refs defined -- in XHTML. -- -- for minimal complete examples see writeDocument and -- runX, the main starting point for running an XML arrow. readDocument :: SysConfigList -> String -> IOStateArrow s b XmlTree -- | the arrow version of readDocument, the arrow input is the -- source URI readFromDocument :: SysConfigList -> IOStateArrow s String XmlTree -- | read a document that is stored in a normal Haskell String -- -- the same function as readDocument, but the parameter forms the input. -- All options available for readDocument are applicable for -- readString, except input encoding options. -- -- Encoding: No decoding is done, the String argument is taken as Unicode -- string All decoding must be done before calling readString, even if -- the XML document contains an encoding spec. readString :: SysConfigList -> String -> IOStateArrow s b XmlTree -- | the arrow version of readString, the arrow input is the source -- URI readFromString :: SysConfigList -> IOStateArrow s String XmlTree -- | parse a string as HTML content, substitute all HTML entity refs and -- canonicalize tree. (substitute char refs, ...). Errors are ignored. -- -- This arrow delegates all work to the parseHtmlContent parser in module -- HtmlParser. -- -- This is a simpler version of readFromString without any -- options, but it does not run in the IO monad. hread :: ArrowXml a => a String XmlTree -- | like hread, but accepts a whole document, not a HTML content hreadDoc :: ArrowXml a => a String XmlTree -- | parse a string as XML CONTENT, (no xml decl or doctype decls are -- allowed), substitute all predefined XML entity refs and canonicalize -- tree This xread arrow delegates all work to the xread parser function -- in module XmlParsec xread :: ArrowXml a => a String XmlTree -- | a more general version of xread which parses a whole document -- including a prolog (xml decl, doctype decl) and processing -- instructions. Doctype decls remain uninterpreted, but are in the list -- of results trees. xreadDoc :: ArrowXml a => a String XmlTree -- | Regular Expression Matcher working on lists of XmlTrees -- -- It's intended to import this module with an explicit import -- declaration for not spoiling the namespace with these somewhat special -- arrows module Text.XML.HXT.Arrow.XmlRegex data XmlRegex mkZero :: String -> XmlRegex mkUnit :: XmlRegex mkPrim :: (XmlTree -> Bool) -> XmlRegex mkPrim' :: (XmlTree -> Bool) -> String -> XmlRegex mkPrimA :: LA XmlTree XmlTree -> XmlRegex mkDot :: XmlRegex mkStar :: XmlRegex -> XmlRegex mkAlt :: XmlRegex -> XmlRegex -> XmlRegex mkAlts :: [XmlRegex] -> XmlRegex mkSeq :: XmlRegex -> XmlRegex -> XmlRegex mkSeqs :: [XmlRegex] -> XmlRegex mkRep :: Int -> XmlRegex -> XmlRegex mkRng :: Int -> Int -> XmlRegex -> XmlRegex mkOpt :: XmlRegex -> XmlRegex mkPerm :: XmlRegex -> XmlRegex -> XmlRegex mkPerms :: [XmlRegex] -> XmlRegex mkMerge :: XmlRegex -> XmlRegex -> XmlRegex nullable :: XmlRegex -> Bool delta :: XmlRegex -> XmlTree -> XmlRegex -- | match a sequence of XML trees with a regular expression over trees -- -- If the input matches, the result is Nothing, else Just an error -- message is returned matchXmlRegex :: XmlRegex -> XmlTrees -> Maybe String -- | split a sequence of XML trees into a pair of a a matching prefix and a -- rest -- -- If there is no matching prefix, Nothing is returned splitXmlRegex :: XmlRegex -> XmlTrees -> Maybe (XmlTrees, XmlTrees) -- | scan a sequence of XML trees and split it into parts matching the -- given regex -- -- If the parts cannot be split because of a missing match, or because of -- the empty sequence as match, Nothing is returned scanXmlRegex :: XmlRegex -> XmlTrees -> Maybe [XmlTrees] -- | check whether a sequence of XmlTrees match an Xml regular expression -- -- The arrow for matchXmlRegex. -- -- The expession is build up from simple arrows acting as predicate -- (mkPrimA) for an XmlTree and of the usual cobinators for -- sequence (mkSeq), repetition (mkStar, mkRep', -- mkRng) and choice (mkAlt, mkOpt) matchRegexA :: XmlRegex -> LA XmlTree XmlTree -> LA XmlTree XmlTrees -- | split the sequence of trees computed by the filter a into -- -- The arrow for splitXmlRegex. -- -- a first part matching the regex and a rest, if a prefix of the input -- sequence does not match the regex, the arrow fails else the pair -- containing the result lists is returned splitRegexA :: XmlRegex -> LA XmlTree XmlTree -> LA XmlTree (XmlTrees, XmlTrees) -- | scan the input sequence with a regex and give the result as a list of -- lists of trees back the regex must at least match one input tree, so -- the empty sequence should not match the regex -- -- The arrow for scanXmlRegex. scanRegexA :: XmlRegex -> LA XmlTree XmlTree -> LA XmlTree XmlTrees instance GHC.Show.Show Text.XML.HXT.Arrow.XmlRegex.XmlRegex -- | De-/Serialisation arrows for XmlTrees and other arbitrary values with -- a Binary instance module Text.XML.HXT.Arrow.Binary readBinaryValue :: (Binary a) => String -> IOStateArrow s b a -- | Serialize a value, optionally compress it, and write it to a file. In -- case of an error, the error message is issued and the arrow fails writeBinaryValue :: (Binary a) => String -> IOStateArrow s a () -- | State arrows for document output module Text.XML.HXT.Arrow.DocumentOutput -- | Write the contents of a document tree into an output stream (file or -- stdout). -- -- If textMode is set, writing is done with Haskell string output, else -- (default) writing is done with lazy ByteString output putXmlDocument :: Bool -> String -> IOStateArrow s XmlTree XmlTree -- | write the tree representation of a document to a file putXmlTree :: String -> IOStateArrow s XmlTree XmlTree -- | write a document with indentaion and line numers putXmlSource :: String -> IOStateArrow s XmlTree XmlTree encodeDocument :: Bool -> Bool -> String -> IOStateArrow s XmlTree XmlTree encodeDocument' :: ArrowXml a => Bool -> Bool -> String -> a XmlTree XmlTree -- | Compound arrow for writing XML documents module Text.XML.HXT.Arrow.WriteDocument -- | the main filter for writing documents -- -- this filter can be configured by an option list like -- readDocument -- -- usage: writeDocument optionList destination -- -- if destination is the empty string or "-", stdout is used -- as output device -- -- for available options see SystemConfig -- -- -- -- a minimal main program for copying a document has the following -- structure: -- --
--   module Main
--   where
--   
--   import Text.XML.HXT.Core
--   
--   main        :: IO ()
--   main
--       = do
--         runX ( readDocument  [] "hello.xml"
--                >>>
--                writeDocument [] "bye.xml"
--              )
--         return ()
--   
-- -- an example for copying a document from the web to standard output with -- global trace level 1, input trace level 2, output encoding isoLatin1, -- and evaluation of error code is: -- --
--   module Main
--   where
--   
--   import Text.XML.HXT.Core
--   import Text.XML.HXT.Curl
--   -- or
--   -- import Text.XML.HXT.HTTP
--   import System.Exit
--   
--   main        :: IO ()
--   main
--       = do
--         [rc] <- runX
--                 ( configSysVars [ withTrace 1          -- set the defaults for all read-,
--                                 , withCurl []          -- write- and other operations
--                                   -- or withHTTP []
--                                 ]
--                   >>>
--                   readDocument  [ withTrace     2      -- use these additional
--                                 , withParseHTML yes    -- options only for this read
--                                 ]
--                                 "http://www.haskell.org/"
--                   >>>
--                   writeDocument [ withOutputEncoding isoLatin1
--                                 ]
--                                 ""                     -- output to stdout
--                   >>>
--                   getErrStatus
--                 )
--         exitWith ( if rc >= c_err
--                    then ExitFailure 1
--                    else ExitSuccess
--                  )
--   
writeDocument :: SysConfigList -> String -> IOStateArrow s XmlTree XmlTree writeDocument' :: Bool -> String -> IOStateArrow s XmlTree XmlTree -- | Convert a document into a string. Formating is done the same way and -- with the same options as in writeDocument. Default output -- encoding is no encoding, that means the result is a normal unicode -- encode haskell string. The default may be overwritten with the -- withOutputEncoding option. The XML PI can be suppressed by the -- a_no_xml_pi option. -- -- This arrow fails, when the encoding scheme is not supported. The arrow -- is pure, it does not run in the IO monad. The XML PI is suppressed, if -- not explicitly turned on with an option (a_no_xml_pi, v_0) writeDocumentToString :: ArrowXml a => SysConfigList -> a XmlTree String -- | indent and format output prepareContents :: ArrowXml a => XIOSysState -> (Bool -> Bool -> String -> a XmlTree XmlTree) -> a XmlTree XmlTree -- | Pickler functions for converting between user defined data types and -- XmlTree data. Usefull for persistent storage and retreival of arbitray -- data as XML documents. -- -- This module is an adaptation of the pickler combinators developed by -- Andrew Kennedy ( -- http://research.microsoft.com/~akenn/fun/picklercombinators.pdf ). -- -- The difference to Kennedys approach is that the target is not a list -- of Chars but a list of XmlTrees. The basic picklers will convert data -- into XML text nodes. New are the picklers for creating elements and -- attributes. -- -- One extension was neccessary: The unpickling may fail. -- -- Old: Therefore the unpickler has a Maybe result type. Failure is used -- to unpickle optional elements (Maybe data) and lists of arbitray -- length. -- -- Since hxt-9.2.0: The unpicklers are implemented as a parser monad with -- an Either err val result type. This enables appropriate error messages -- , when unpickling XML stuff, that is not generated with the picklers -- and which contains some elements and/or attributes that are not -- handled when unpickling. -- -- There is an example program demonstrating the use of the picklers for -- a none trivial data structure. (see "examples/arrows/pickle" directory -- in the hxt distribution) module Text.XML.HXT.Arrow.Pickle.Xml data St St :: [XmlTree] -> [XmlTree] -> Int -> QName -> Bool -> St [attributes] :: St -> [XmlTree] [contents] :: St -> [XmlTree] [nesting] :: St -> Int [pname] :: St -> QName [pelem] :: St -> Bool data PU a PU :: Pickler a -> Unpickler a -> Schema -> PU a [appPickle] :: PU a -> Pickler a [appUnPickle] :: PU a -> Unpickler a [theSchema] :: PU a -> Schema type Pickler a = a -> St -> St newtype Unpickler a UP :: (St -> (UnpickleVal a, St)) -> Unpickler a [runUP] :: Unpickler a -> St -> (UnpickleVal a, St) type UnpickleVal a = Either UnpickleErr a type UnpickleErr = (String, St) throwMsg :: String -> Unpickler a -- | Choice combinator for unpickling -- -- first 2 arguments are applied sequentially, but if the 1. one fails -- the 3. arg is applied mchoice :: Unpickler a -> (a -> Unpickler b) -> Unpickler b -> Unpickler b -- | Lift a Maybe value into the Unpickler monad. -- -- The 1. arg is the attached error message liftMaybe :: String -> Maybe a -> Unpickler a -- | Lift an Either value into the Unpickler monad liftUnpickleVal :: UnpickleVal a -> Unpickler a getCont :: Unpickler XmlTree getAtt :: QName -> Unpickler XmlTree getNSAtt :: String -> Unpickler () emptySt :: St putAtt :: QName -> [XmlTree] -> St -> St putCont :: XmlTree -> St -> St findElem :: (a -> Bool) -> [a] -> Maybe (a, [a]) -- | Format the context of an error message. formatSt :: St -> String -- | conversion of an arbitrary value into an XML document tree. -- -- The pickler, first parameter, controls the conversion process. Result -- is a complete document tree including a root node pickleDoc :: PU a -> a -> XmlTree -- | Conversion of an XML document tree into an arbitrary data type -- -- The inverse of pickleDoc. This law should hold for all -- picklers: unpickle px . pickle px $ v == Just v . Not every -- possible combination of picklers does make sense. For reconverting a -- value from an XML tree, is becomes neccessary, to introduce "enough" -- markup for unpickling the value unpickleDoc :: PU a -> XmlTree -> Maybe a -- | Like unpickleDoc but with a (sometimes) useful error message, when -- unpickling failed. unpickleDoc' :: PU a -> XmlTree -> Either String a -- | The main entry for unpickling, called by unpickleDoc unpickleElem' :: PU a -> Int -> XmlTree -> UnpickleVal a -- | Pickles a value, then writes the document to a string. showPickled :: (XmlPickler a) => SysConfigList -> a -> String -- | The zero pickler -- -- Encodes nothing, fails always during unpickling xpZero :: String -> PU a -- | unit pickler xpUnit :: PU () -- | Check EOF pickler. -- -- When pickling, this behaves like the unit pickler. The unpickler -- fails, when there is some unprocessed XML contents left. xpCheckEmptyContents :: PU a -> PU a -- | Like xpCheckEmptyContents, but checks the attribute list xpCheckEmptyAttributes :: PU a -> PU a -- | Composition of xpCheckEmptyContents and xpCheckAttributes xpCheckEmpty :: PU a -> PU a xpLift :: a -> PU a -- | Lift a Maybe value to a pickler. -- -- Nothing is mapped to the zero pickler, Just x is -- pickled with xpLift x. xpLiftMaybe :: Maybe a -> PU a xpLiftEither :: Either String a -> PU a -- | Combine two picklers sequentially. -- -- If the first fails during unpickling, the whole unpickler fails xpSeq :: (b -> a) -> PU a -> (a -> PU b) -> PU b -- | First apply a fixed pickler/unpickler, then a 2. one -- -- If the first fails during unpickling, the whole pickler fails. This -- can be used to check some properties of the input, e.g. whether a -- given fixed attribute or a namespace declaration exists -- (xpAddFixedAttr, xpAddNSDecl) or to filter the input, -- e.g. to ignore some elements or attributes (xpFilterCont, -- xpFilterAttr). -- -- When pickling, this can be used to insert some fixed XML pieces, e.g. -- namespace declarations, class attributes or other stuff. xpSeq' :: PU () -> PU a -> PU a -- | combine tow picklers with a choice -- -- Run two picklers in sequence like with xpSeq. If during unpickling the -- first one fails, an alternative pickler (first argument) is applied. -- This pickler is only used as combinator for unpickling. xpChoice :: PU b -> PU a -> (a -> PU b) -> Unpickler b -- | map value into another domain and apply pickler there -- -- One of the most often used picklers. xpWrap :: (a -> b, b -> a) -> PU a -> PU b -- | like xpWrap, but if the inverse mapping is undefined, the -- unpickler fails -- -- Map a value into another domain. If the inverse mapping is undefined -- (Nothing), the unpickler fails -- -- Deprecated: Use xpWrapEither, this gives better error messages xpWrapMaybe :: (a -> Maybe b, b -> a) -> PU a -> PU b -- | like xpWrap, but if the inverse mapping is undefined, the -- unpickler fails -- -- Map a value into another domain. If the inverse mapping is undefined, -- the unpickler fails with an error message in the Left component xpWrapEither :: (a -> Either String b, b -> a) -> PU a -> PU b -- | pickle a pair of values sequentially -- -- Used for pairs or together with wrap for pickling algebraic data types -- with two components xpPair :: PU a -> PU b -> PU (a, b) -- | Like xpPair but for triples xpTriple :: PU a -> PU b -> PU c -> PU (a, b, c) -- | Like xpPair and xpTriple but for 4-tuples xp4Tuple :: PU a -> PU b -> PU c -> PU d -> PU (a, b, c, d) -- | Like xpPair and xpTriple but for 5-tuples xp5Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU (a, b, c, d, e) -- | Like xpPair and xpTriple but for 6-tuples xp6Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU (a, b, c, d, e, f) -- | Like xpPair and xpTriple but for 7-tuples -- -- Thanks to Tony Morris for doing xp7Tuple, ..., xp24Tuple. xp7Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU (a, b, c, d, e, f, g) xp8Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU h -> PU (a, b, c, d, e, f, g, h) xp9Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU h -> PU i -> PU (a, b, c, d, e, f, g, h, i) xp10Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU h -> PU i -> PU j -> PU (a, b, c, d, e, f, g, h, i, j) xp11Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU h -> PU i -> PU j -> PU k -> PU (a, b, c, d, e, f, g, h, i, j, k) xp12Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU h -> PU i -> PU j -> PU k -> PU l -> PU (a, b, c, d, e, f, g, h, i, j, k, l) xp13Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU h -> PU i -> PU j -> PU k -> PU l -> PU m -> PU (a, b, c, d, e, f, g, h, i, j, k, l, m) xp14Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU h -> PU i -> PU j -> PU k -> PU l -> PU m -> PU n -> PU (a, b, c, d, e, f, g, h, i, j, k, l, m, n) xp15Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU h -> PU i -> PU j -> PU k -> PU l -> PU m -> PU n -> PU o -> PU (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) xp16Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU h -> PU i -> PU j -> PU k -> PU l -> PU m -> PU n -> PU o -> PU p -> PU (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) xp17Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU h -> PU i -> PU j -> PU k -> PU l -> PU m -> PU n -> PU o -> PU p -> PU q -> PU (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q) xp18Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU h -> PU i -> PU j -> PU k -> PU l -> PU m -> PU n -> PU o -> PU p -> PU q -> PU r -> PU (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r) xp19Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU h -> PU i -> PU j -> PU k -> PU l -> PU m -> PU n -> PU o -> PU p -> PU q -> PU r -> PU s -> PU (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s) xp20Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU h -> PU i -> PU j -> PU k -> PU l -> PU m -> PU n -> PU o -> PU p -> PU q -> PU r -> PU s -> PU t -> PU (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t) xp21Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU h -> PU i -> PU j -> PU k -> PU l -> PU m -> PU n -> PU o -> PU p -> PU q -> PU r -> PU s -> PU t -> PU u -> PU (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u) xp22Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU h -> PU i -> PU j -> PU k -> PU l -> PU m -> PU n -> PU o -> PU p -> PU q -> PU r -> PU s -> PU t -> PU u -> PU v -> PU (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v) xp23Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU h -> PU i -> PU j -> PU k -> PU l -> PU m -> PU n -> PU o -> PU p -> PU q -> PU r -> PU s -> PU t -> PU u -> PU v -> PU w -> PU (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w) -- | Hopefully no one needs a xp25Tuple xp24Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU h -> PU i -> PU j -> PU k -> PU l -> PU m -> PU n -> PU o -> PU p -> PU q -> PU r -> PU s -> PU t -> PU u -> PU v -> PU w -> PU x -> PU (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x) -- | Pickle a string into an XML text node -- -- One of the most often used primitive picklers. Attention: For pickling -- empty strings use xpText0. If the text has a more specific -- datatype than xsd:string, use xpTextDT xpText :: PU String -- | Pickle a string into an XML text node -- -- Text pickler with a description of the structure of the text by a -- schema. A schema for a data type can be defined by scDT. In -- Schema there are some more functions for creating simple -- datatype descriptions. xpTextDT :: Schema -> PU String -- | Pickle a possibly empty string into an XML node. -- -- Must be used in all places, where empty strings are legal values. If -- the content of an element can be an empty string, this string -- disapears during storing the DOM into a document and reparse the -- document. So the empty text node becomes nothing, and the pickler must -- deliver an empty string, if there is no text node in the document. xpText0 :: PU String -- | Pickle a possibly empty string with a datatype description into an XML -- node. -- -- Like xpText0 but with extra Parameter for datatype description -- as in xpTextDT. xpText0DT :: Schema -> PU String -- | Pickle an arbitrary value by applyling show during pickling and read -- during unpickling. -- -- Real pickling is then done with xpText. One of the most often -- used pimitive picklers. Applicable for all types which are instances -- of Read and Show xpPrim :: (Read a, Show a) => PU a -- | Pickle an Int xpInt :: PU Int -- | Pickle an XmlTree by just adding it -- -- Usefull for components of type XmlTree in other data structures xpTree :: PU XmlTree -- | Pickle a whole list of XmlTrees by just adding the list, unpickle is -- done by taking all element contents. -- -- This pickler should always be combined with xpElem for taking -- the whole contents of an element. xpTrees :: PU [XmlTree] -- | Pickle a string representing XML contents by inserting the tree -- representation into the XML document. -- -- Unpickling is done by converting the contents with -- xshowEscapeXml into a string, this function will escape all XML -- special chars, such that pickling the value back becomes save. -- Pickling is done with xread xpXmlText :: PU String -- | Encoding of optional data by ignoring the Nothing case during pickling -- and relying on failure during unpickling to recompute the Nothing case -- -- The default pickler for Maybe types xpOption :: PU a -> PU (Maybe a) -- | Optional conversion with default value -- -- The default value is not encoded in the XML document, during -- unpickling the default value is inserted if the pickler fails xpDefault :: (Eq a) => a -> PU a -> PU a -- | Encoding of list values by pickling all list elements sequentially. -- -- Unpickler relies on failure for detecting the end of the list. The -- standard pickler for lists. Can also be used in combination with -- xpWrap for constructing set and map picklers xpList :: PU a -> PU [a] -- | Encoding of a none empty list of values -- -- Attention: when calling this pickler with an empty list, an internal -- error "head of empty list is raised". xpList1 :: PU a -> PU [a] -- | Standard pickler for maps -- -- This pickler converts a map into a list of pairs. All key value pairs -- are mapped to an element with name (1.arg), the key is encoded as an -- attribute named by the 2. argument, the 3. arg is the pickler for the -- keys, the last one for the values xpMap :: Ord k => String -> String -> PU k -> PU v -> PU (Map k v) -- | Pickler for sum data types. -- -- Every constructor is mapped to an index into the list of picklers. The -- index is used only during pickling, not during unpickling, there the -- 1. match is taken xpAlt :: (a -> Int) -> [PU a] -> PU a -- | Pickler for wrapping/unwrapping data into an XML element -- -- Extra parameter is the element name given as a QName. THE pickler for -- constructing nested structures -- -- Example: -- --
--   xpElemQN (mkName "number") $ xpickle
--   
-- -- will map an (42::Int) onto -- --
--   <number>42</number>
--   
xpElemQN :: QName -> PU a -> PU a -- | convenient Pickler for xpElemQN -- --
--   xpElem n = xpElemQN (mkName n)
--   
xpElem :: String -> PU a -> PU a -- | convenient Pickler for xpElemQN for pickling elements with respect to -- namespaces -- --
--   xpElemNS ns px lp = xpElemQN (mkQName px lp ns)
--   
xpElemNS :: String -> String -> String -> PU a -> PU a -- | Pickler for wrapping/unwrapping data into an XML element with an -- attribute with given value -- -- To make XML structures flexible but limit the number of different -- elements, it's sometimes useful to use a kind of generic element with -- a key value structure -- -- Example: -- --
--   <attr name="key1">value1</attr>
--   <attr name="key2">value2</attr>
--   <attr name="key3">value3</attr>
--   
-- -- the Haskell datatype may look like this -- --
--   type T = T { key1 :: Int ; key2 :: String ; key3 :: Double }
--   
-- -- Then the picker for that type looks like this -- --
--   xpT :: PU T
--   xpT = xpWrap ( uncurry3 T, \ t -> (key1 t, key2 t, key3 t) ) $
--         xpTriple (xpElemWithAttrValue "attr" "name" "key1" $ xpickle)
--                  (xpElemWithAttrValue "attr" "name" "key2" $ xpText0)
--                  (xpElemWithAttrValue "attr" "name" "key3" $ xpickle)
--   
xpElemWithAttrValue :: String -> String -> String -> PU a -> PU a -- | Pickler for storing/retreiving data into/from an attribute value -- -- The attribute is inserted in the surrounding element constructed by -- the xpElem pickler xpAttrQN :: QName -> PU a -> PU a -- | convenient Pickler for xpAttrQN -- --
--   xpAttr n = xpAttrQN (mkName n)
--   
xpAttr :: String -> PU a -> PU a -- | convenient Pickler for xpAttrQN -- --
--   xpAttr ns px lp = xpAttrQN (mkQName px lp ns)
--   
xpAttrNS :: String -> String -> String -> PU a -> PU a -- | A text attribute. xpTextAttr :: String -> PU String -- | Add an optional attribute for an optional value (Maybe a). xpAttrImplied :: String -> PU a -> PU (Maybe a) xpAttrFixed :: String -> String -> PU () -- | Add/Check an attribute with a fixed value. xpAddFixedAttr :: String -> String -> PU a -> PU a -- | Add a namespace declaration. -- -- When generating XML the namespace decl is added, when reading a -- document, the unpickler checks whether there is a namespace -- declaration for the given namespace URI (2. arg) xpAddNSDecl :: String -> String -> PU a -> PU a xpAttrNSDecl :: String -> String -> PU () xpIgnoreCont :: LA XmlTree XmlTree -> PU () xpIgnoreAttr :: LA XmlTree XmlTree -> PU () -- | When unpickling, filter the contents of the element currently -- processed, before applying the pickler argument -- -- Maybe useful to ignore some stuff in the input, or to do some cleanup -- before unpickling. xpFilterCont :: LA XmlTree XmlTree -> PU a -> PU a -- | Same as xpFilterCont but for the attribute list of the element -- currently processed. -- -- Maybe useful to ignore some stuff in the input, e.g. class attributes, -- or to do some cleanup before unpickling. xpFilterAttr :: LA XmlTree XmlTree -> PU a -> PU a xpIgnoreInput :: (([XmlTree] -> [XmlTree]) -> St -> St) -> LA XmlTree XmlTree -> PU () -- | The class for overloading xpickle, the default pickler class XmlPickler a xpickle :: XmlPickler a => PU a instance GHC.Show.Show Text.XML.HXT.Arrow.Pickle.Xml.St instance GHC.Base.Functor Text.XML.HXT.Arrow.Pickle.Xml.Unpickler instance GHC.Base.Applicative Text.XML.HXT.Arrow.Pickle.Xml.Unpickler instance GHC.Base.Monad Text.XML.HXT.Arrow.Pickle.Xml.Unpickler instance Control.Monad.State.Class.MonadState Text.XML.HXT.Arrow.Pickle.Xml.St Text.XML.HXT.Arrow.Pickle.Xml.Unpickler instance Control.Monad.Error.Class.MonadError Text.XML.HXT.Arrow.Pickle.Xml.UnpickleErr Text.XML.HXT.Arrow.Pickle.Xml.Unpickler instance Text.XML.HXT.Arrow.Pickle.Xml.XmlPickler GHC.Types.Int instance Text.XML.HXT.Arrow.Pickle.Xml.XmlPickler GHC.Integer.Type.Integer instance Text.XML.HXT.Arrow.Pickle.Xml.XmlPickler () instance (Text.XML.HXT.Arrow.Pickle.Xml.XmlPickler a, Text.XML.HXT.Arrow.Pickle.Xml.XmlPickler b) => Text.XML.HXT.Arrow.Pickle.Xml.XmlPickler (a, b) instance (Text.XML.HXT.Arrow.Pickle.Xml.XmlPickler a, Text.XML.HXT.Arrow.Pickle.Xml.XmlPickler b, Text.XML.HXT.Arrow.Pickle.Xml.XmlPickler c) => Text.XML.HXT.Arrow.Pickle.Xml.XmlPickler (a, b, c) instance (Text.XML.HXT.Arrow.Pickle.Xml.XmlPickler a, Text.XML.HXT.Arrow.Pickle.Xml.XmlPickler b, Text.XML.HXT.Arrow.Pickle.Xml.XmlPickler c, Text.XML.HXT.Arrow.Pickle.Xml.XmlPickler d) => Text.XML.HXT.Arrow.Pickle.Xml.XmlPickler (a, b, c, d) instance (Text.XML.HXT.Arrow.Pickle.Xml.XmlPickler a, Text.XML.HXT.Arrow.Pickle.Xml.XmlPickler b, Text.XML.HXT.Arrow.Pickle.Xml.XmlPickler c, Text.XML.HXT.Arrow.Pickle.Xml.XmlPickler d, Text.XML.HXT.Arrow.Pickle.Xml.XmlPickler e) => Text.XML.HXT.Arrow.Pickle.Xml.XmlPickler (a, b, c, d, e) instance Text.XML.HXT.Arrow.Pickle.Xml.XmlPickler a => Text.XML.HXT.Arrow.Pickle.Xml.XmlPickler [a] instance Text.XML.HXT.Arrow.Pickle.Xml.XmlPickler a => Text.XML.HXT.Arrow.Pickle.Xml.XmlPickler (GHC.Base.Maybe a) -- | Pickler functions for converting between user defined data types and -- XmlTree data. Usefull for persistent storage and retreival of arbitray -- data as XML documents -- -- This module is an adaptation of the pickler combinators developed by -- Andrew Kennedy ( -- http://research.microsoft.com/~akenn/fun/picklercombinators.pdf ) -- -- The difference to Kennedys approach is that the target is not a list -- of Chars but a list of XmlTrees. The basic picklers will convert data -- into XML text nodes. New are the picklers for creating elements and -- attributes. -- -- One extension was neccessary: The unpickling may fail. Therefore the -- unpickler has a Maybe result type. Failure is used to unpickle -- optional elements (Maybe data) and lists of arbitray length -- -- There is an example program demonstrating the use of the picklers for -- a none trivial data structure. (see "examples/arrows/pickle" -- directory) module Text.XML.HXT.Arrow.Pickle -- | store an arbitray value in a persistent XML document -- -- The pickler converts a value into an XML tree, this is written out -- with writeDocument. The option list is passed to -- writeDocument -- -- An option evaluated by this arrow is a_addDTD. If -- a_addDTD is set (v_1), the pickler DTD is added as an -- inline DTD into the document. xpickleDocument :: PU a -> SysConfigList -> String -> IOStateArrow s a XmlTree -- | read an arbitray value from an XML document -- -- The document is read with readDocument. Options are passed to -- readDocument. The conversion from XmlTree is done with the -- pickler. -- -- xpickleDocument xp al dest >>> xunpickleDocument xp al' -- dest is the identity arrow when applied with the appropriate -- options. When during pickling indentation is switched on, the -- whitespace must be removed during unpickling. xunpickleDocument :: PU a -> SysConfigList -> String -> IOStateArrow s b a -- | Write out the DTD generated out of a pickler. Calls -- xpicklerDTD xpickleWriteDTD :: PU b -> SysConfigList -> String -> IOStateArrow s b XmlTree -- | The arrow for generating the DTD out of a pickler -- -- A DTD is generated from a pickler and check for consistency. Errors -- concerning the DTD are issued. xpickleDTD :: PU b -> IOStateArrow s b XmlTree -- | An arrow for checking picklers -- -- A value is transformed into an XML document by a given pickler, the -- associated DTD is extracted from the pickler and checked, the document -- including the DTD is tranlated into a string, this string is read and -- validated against the included DTD, and unpickled. The last step is -- the equality with the input. -- -- If the check succeeds, the arrow works like this, else it fails. checkPickler :: Eq a => PU a -> IOStateArrow s a a -- | The arrow version of the pickler function xpickleVal :: ArrowXml a => PU b -> a b XmlTree -- | The arrow version of the unpickler function xunpickleVal :: PU b -> IOStateArrow s XmlTree b -- | Compute the associated DTD of a pickler thePicklerDTD :: PU b -> XmlTrees -- | Option for generating and adding DTD when document is pickled a_addDTD :: String -- | conversion of an arbitrary value into an XML document tree. -- -- The pickler, first parameter, controls the conversion process. Result -- is a complete document tree including a root node pickleDoc :: PU a -> a -> XmlTree -- | Conversion of an XML document tree into an arbitrary data type -- -- The inverse of pickleDoc. This law should hold for all -- picklers: unpickle px . pickle px $ v == Just v . Not every -- possible combination of picklers does make sense. For reconverting a -- value from an XML tree, is becomes neccessary, to introduce "enough" -- markup for unpickling the value unpickleDoc :: PU a -> XmlTree -> Maybe a -- | Like unpickleDoc but with a (sometimes) useful error message, when -- unpickling failed. unpickleDoc' :: PU a -> XmlTree -> Either String a -- | Pickles a value, then writes the document to a string. showPickled :: (XmlPickler a) => SysConfigList -> a -> String data PU a PU :: Pickler a -> Unpickler a -> Schema -> PU a [appPickle] :: PU a -> Pickler a [appUnPickle] :: PU a -> Unpickler a [theSchema] :: PU a -> Schema -- | The class for overloading xpickle, the default pickler class XmlPickler a xpickle :: XmlPickler a => PU a -- | Like xpPair and xpTriple but for 4-tuples xp4Tuple :: PU a -> PU b -> PU c -> PU d -> PU (a, b, c, d) -- | Like xpPair and xpTriple but for 5-tuples xp5Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU (a, b, c, d, e) -- | Like xpPair and xpTriple but for 6-tuples xp6Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU (a, b, c, d, e, f) -- | Like xpPair and xpTriple but for 7-tuples -- -- Thanks to Tony Morris for doing xp7Tuple, ..., xp24Tuple. xp7Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU (a, b, c, d, e, f, g) xp8Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU h -> PU (a, b, c, d, e, f, g, h) xp9Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU h -> PU i -> PU (a, b, c, d, e, f, g, h, i) xp10Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU h -> PU i -> PU j -> PU (a, b, c, d, e, f, g, h, i, j) xp11Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU h -> PU i -> PU j -> PU k -> PU (a, b, c, d, e, f, g, h, i, j, k) xp12Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU h -> PU i -> PU j -> PU k -> PU l -> PU (a, b, c, d, e, f, g, h, i, j, k, l) xp13Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU h -> PU i -> PU j -> PU k -> PU l -> PU m -> PU (a, b, c, d, e, f, g, h, i, j, k, l, m) xp14Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU h -> PU i -> PU j -> PU k -> PU l -> PU m -> PU n -> PU (a, b, c, d, e, f, g, h, i, j, k, l, m, n) xp15Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU h -> PU i -> PU j -> PU k -> PU l -> PU m -> PU n -> PU o -> PU (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) xp16Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU h -> PU i -> PU j -> PU k -> PU l -> PU m -> PU n -> PU o -> PU p -> PU (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) xp17Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU h -> PU i -> PU j -> PU k -> PU l -> PU m -> PU n -> PU o -> PU p -> PU q -> PU (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q) xp18Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU h -> PU i -> PU j -> PU k -> PU l -> PU m -> PU n -> PU o -> PU p -> PU q -> PU r -> PU (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r) xp19Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU h -> PU i -> PU j -> PU k -> PU l -> PU m -> PU n -> PU o -> PU p -> PU q -> PU r -> PU s -> PU (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s) xp20Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU h -> PU i -> PU j -> PU k -> PU l -> PU m -> PU n -> PU o -> PU p -> PU q -> PU r -> PU s -> PU t -> PU (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t) xp21Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU h -> PU i -> PU j -> PU k -> PU l -> PU m -> PU n -> PU o -> PU p -> PU q -> PU r -> PU s -> PU t -> PU u -> PU (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u) xp22Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU h -> PU i -> PU j -> PU k -> PU l -> PU m -> PU n -> PU o -> PU p -> PU q -> PU r -> PU s -> PU t -> PU u -> PU v -> PU (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v) xp23Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU h -> PU i -> PU j -> PU k -> PU l -> PU m -> PU n -> PU o -> PU p -> PU q -> PU r -> PU s -> PU t -> PU u -> PU v -> PU w -> PU (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w) -- | Hopefully no one needs a xp25Tuple xp24Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU h -> PU i -> PU j -> PU k -> PU l -> PU m -> PU n -> PU o -> PU p -> PU q -> PU r -> PU s -> PU t -> PU u -> PU v -> PU w -> PU x -> PU (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x) -- | Add/Check an attribute with a fixed value. xpAddFixedAttr :: String -> String -> PU a -> PU a -- | Add a namespace declaration. -- -- When generating XML the namespace decl is added, when reading a -- document, the unpickler checks whether there is a namespace -- declaration for the given namespace URI (2. arg) xpAddNSDecl :: String -> String -> PU a -> PU a -- | Pickler for sum data types. -- -- Every constructor is mapped to an index into the list of picklers. The -- index is used only during pickling, not during unpickling, there the -- 1. match is taken xpAlt :: (a -> Int) -> [PU a] -> PU a -- | convenient Pickler for xpAttrQN -- --
--   xpAttr n = xpAttrQN (mkName n)
--   
xpAttr :: String -> PU a -> PU a xpAttrFixed :: String -> String -> PU () -- | Add an optional attribute for an optional value (Maybe a). xpAttrImplied :: String -> PU a -> PU (Maybe a) -- | convenient Pickler for xpAttrQN -- --
--   xpAttr ns px lp = xpAttrQN (mkQName px lp ns)
--   
xpAttrNS :: String -> String -> String -> PU a -> PU a -- | Composition of xpCheckEmptyContents and xpCheckAttributes xpCheckEmpty :: PU a -> PU a -- | Like xpCheckEmptyContents, but checks the attribute list xpCheckEmptyAttributes :: PU a -> PU a -- | Check EOF pickler. -- -- When pickling, this behaves like the unit pickler. The unpickler -- fails, when there is some unprocessed XML contents left. xpCheckEmptyContents :: PU a -> PU a -- | A text attribute. xpTextAttr :: String -> PU String -- | combine tow picklers with a choice -- -- Run two picklers in sequence like with xpSeq. If during unpickling the -- first one fails, an alternative pickler (first argument) is applied. -- This pickler is only used as combinator for unpickling. xpChoice :: PU b -> PU a -> (a -> PU b) -> Unpickler b -- | Optional conversion with default value -- -- The default value is not encoded in the XML document, during -- unpickling the default value is inserted if the pickler fails xpDefault :: (Eq a) => a -> PU a -> PU a -- | convenient Pickler for xpElemQN -- --
--   xpElem n = xpElemQN (mkName n)
--   
xpElem :: String -> PU a -> PU a -- | convenient Pickler for xpElemQN for pickling elements with respect to -- namespaces -- --
--   xpElemNS ns px lp = xpElemQN (mkQName px lp ns)
--   
xpElemNS :: String -> String -> String -> PU a -> PU a -- | Pickler for wrapping/unwrapping data into an XML element with an -- attribute with given value -- -- To make XML structures flexible but limit the number of different -- elements, it's sometimes useful to use a kind of generic element with -- a key value structure -- -- Example: -- --
--   <attr name="key1">value1</attr>
--   <attr name="key2">value2</attr>
--   <attr name="key3">value3</attr>
--   
-- -- the Haskell datatype may look like this -- --
--   type T = T { key1 :: Int ; key2 :: String ; key3 :: Double }
--   
-- -- Then the picker for that type looks like this -- --
--   xpT :: PU T
--   xpT = xpWrap ( uncurry3 T, \ t -> (key1 t, key2 t, key3 t) ) $
--         xpTriple (xpElemWithAttrValue "attr" "name" "key1" $ xpickle)
--                  (xpElemWithAttrValue "attr" "name" "key2" $ xpText0)
--                  (xpElemWithAttrValue "attr" "name" "key3" $ xpickle)
--   
xpElemWithAttrValue :: String -> String -> String -> PU a -> PU a -- | Same as xpFilterCont but for the attribute list of the element -- currently processed. -- -- Maybe useful to ignore some stuff in the input, e.g. class attributes, -- or to do some cleanup before unpickling. xpFilterAttr :: LA XmlTree XmlTree -> PU a -> PU a -- | When unpickling, filter the contents of the element currently -- processed, before applying the pickler argument -- -- Maybe useful to ignore some stuff in the input, or to do some cleanup -- before unpickling. xpFilterCont :: LA XmlTree XmlTree -> PU a -> PU a -- | Pickle an Int xpInt :: PU Int xpLift :: a -> PU a xpLiftEither :: Either String a -> PU a -- | Lift a Maybe value to a pickler. -- -- Nothing is mapped to the zero pickler, Just x is -- pickled with xpLift x. xpLiftMaybe :: Maybe a -> PU a -- | Encoding of list values by pickling all list elements sequentially. -- -- Unpickler relies on failure for detecting the end of the list. The -- standard pickler for lists. Can also be used in combination with -- xpWrap for constructing set and map picklers xpList :: PU a -> PU [a] -- | Encoding of a none empty list of values -- -- Attention: when calling this pickler with an empty list, an internal -- error "head of empty list is raised". xpList1 :: PU a -> PU [a] -- | Standard pickler for maps -- -- This pickler converts a map into a list of pairs. All key value pairs -- are mapped to an element with name (1.arg), the key is encoded as an -- attribute named by the 2. argument, the 3. arg is the pickler for the -- keys, the last one for the values xpMap :: Ord k => String -> String -> PU k -> PU v -> PU (Map k v) -- | Encoding of optional data by ignoring the Nothing case during pickling -- and relying on failure during unpickling to recompute the Nothing case -- -- The default pickler for Maybe types xpOption :: PU a -> PU (Maybe a) -- | pickle a pair of values sequentially -- -- Used for pairs or together with wrap for pickling algebraic data types -- with two components xpPair :: PU a -> PU b -> PU (a, b) -- | Pickle an arbitrary value by applyling show during pickling and read -- during unpickling. -- -- Real pickling is then done with xpText. One of the most often -- used pimitive picklers. Applicable for all types which are instances -- of Read and Show xpPrim :: (Read a, Show a) => PU a -- | Combine two picklers sequentially. -- -- If the first fails during unpickling, the whole unpickler fails xpSeq :: (b -> a) -> PU a -> (a -> PU b) -> PU b -- | First apply a fixed pickler/unpickler, then a 2. one -- -- If the first fails during unpickling, the whole pickler fails. This -- can be used to check some properties of the input, e.g. whether a -- given fixed attribute or a namespace declaration exists -- (xpAddFixedAttr, xpAddNSDecl) or to filter the input, -- e.g. to ignore some elements or attributes (xpFilterCont, -- xpFilterAttr). -- -- When pickling, this can be used to insert some fixed XML pieces, e.g. -- namespace declarations, class attributes or other stuff. xpSeq' :: PU () -> PU a -> PU a -- | Pickle a string into an XML text node -- -- One of the most often used primitive picklers. Attention: For pickling -- empty strings use xpText0. If the text has a more specific -- datatype than xsd:string, use xpTextDT xpText :: PU String -- | Pickle a possibly empty string into an XML node. -- -- Must be used in all places, where empty strings are legal values. If -- the content of an element can be an empty string, this string -- disapears during storing the DOM into a document and reparse the -- document. So the empty text node becomes nothing, and the pickler must -- deliver an empty string, if there is no text node in the document. xpText0 :: PU String -- | Pickle a string into an XML text node -- -- Text pickler with a description of the structure of the text by a -- schema. A schema for a data type can be defined by scDT. In -- Schema there are some more functions for creating simple -- datatype descriptions. xpTextDT :: Schema -> PU String -- | Pickle a possibly empty string with a datatype description into an XML -- node. -- -- Like xpText0 but with extra Parameter for datatype description -- as in xpTextDT. xpText0DT :: Schema -> PU String -- | Pickle an XmlTree by just adding it -- -- Usefull for components of type XmlTree in other data structures xpTree :: PU XmlTree -- | Pickle a whole list of XmlTrees by just adding the list, unpickle is -- done by taking all element contents. -- -- This pickler should always be combined with xpElem for taking -- the whole contents of an element. xpTrees :: PU [XmlTree] -- | Like xpPair but for triples xpTriple :: PU a -> PU b -> PU c -> PU (a, b, c) -- | unit pickler xpUnit :: PU () -- | map value into another domain and apply pickler there -- -- One of the most often used picklers. xpWrap :: (a -> b, b -> a) -> PU a -> PU b -- | like xpWrap, but if the inverse mapping is undefined, the -- unpickler fails -- -- Map a value into another domain. If the inverse mapping is undefined, -- the unpickler fails with an error message in the Left component xpWrapEither :: (a -> Either String b, b -> a) -> PU a -> PU b -- | like xpWrap, but if the inverse mapping is undefined, the -- unpickler fails -- -- Map a value into another domain. If the inverse mapping is undefined -- (Nothing), the unpickler fails -- -- Deprecated: Use xpWrapEither, this gives better error messages xpWrapMaybe :: (a -> Maybe b, b -> a) -> PU a -> PU b -- | Pickle a string representing XML contents by inserting the tree -- representation into the XML document. -- -- Unpickling is done by converting the contents with -- xshowEscapeXml into a string, this function will escape all XML -- special chars, such that pickling the value back becomes save. -- Pickling is done with xread xpXmlText :: PU String -- | The zero pickler -- -- Encodes nothing, fails always during unpickling xpZero :: String -> PU a -- | The datatype for modelling the structure of an data Schema type Schemas = [Schema] data DataTypeDescr -- | The HXT arrow interface -- -- The application programming interface to the arrow modules of the -- Haskell XML Toolbox. This module exports all important arrows for -- input, output, parsing, validating and transforming XML. It also -- exports all basic datatypes and functions of the toolbox. module Text.XML.HXT.Core