
Hi Mads,
I am trying to use HXT to evaluate XPath expressions. The XPath expressions are not specified by myself, but by users of my program. However, the idea behind HXT's error handling confuses me. Maybe somebody can enlighten me.
This program fragment:
evalXPath :: String -> String -> [XmlTree] evalXPath xpath xml = runLA ( xread >>> propagateNamespaces >>> getXPathTrees xpath ) xml
seems to work fine, except when it comes to error handling. If the xml-string is malformed, the error is simply ignored and the evalXPath-function just returns an empty list. I can understand what happens. 'getXPathTrees xpath' tries to match the xpath to a XmlTree which represents a parse error, and it therefore never matches anything.
When calling evalXPath, there are 2 error situations. Both can be handled
in the same form.
1. xread is called with a string, that does not match XML contents.
This results in a single element list containing an error message.
Test: runLA xread "<???>"
The following arrows, propagateNamespaces ..., don't accept error messages,
so they fail and the result of the whole arrow ist the empty list.
So the result of xread must be checked before further processed.
2. getXPathTrees xpath can fail with a syntax error in xpath.
This again results in a single element list with an error message.
The error message can be catched in the same way as before.
Your example can be rewritten in the following way:
----------------------------------
module NameSpace
where
import Text.XML.HXT.Arrow
import Text.XML.HXT.XPath
simpleXml :: String
simpleXml = "
What I really would like was functions like:
parseStr :: (Monad m) => String -> m XmlTrees parseStr xml = case Parsec.xread xml of (x:xs) -> if (Dom.isError x) then fail "Could not parse tree" else return (x:xs) [] -> fail "No XML tree resultet from parsing XML"
You already do have this. Not in a monadic version but as arrow. See above example.
And a similar function for the XPath. This could also speed up my program, as I would not parse the same XPath again and again. A
This is a right point. Here the current XPath calling interface is too simple. A separation into XPath parsing and evaluation would be more flexible. The parsing (and error handling of XPath syntax errors) could be done once. I will extend the interface to support this. Thanks for your comments and hints, Uwe