Snap: rendering table with compiled splices - haskell

Well, this is another obstacle with compiled splices that I struggle to overcome.
I had some trouble when I first did it with the original interpreted splices and now I am stuck translating it to compiled variant.
The original problem is described here: rendering a table
So I need to build this kind of structure:
map (\doc -> fmap (\f -> splice $ f at doc) fields ) documents
which is just just external and internal loops, the outer rendering raws and the inner rendering cells. It is all described in the original link.
It is currently implemented in interpreted mode like this:
tableRawS raw = mapSplices (\f -> tableCellS $ T.pack $ at f raw) (tableFields table)
where tableCellS cell = runChildrenWithText $ "table-cell" ## cell
tableBodyS = mapSplices (\d -> runChildrenWith $ raws d) documents
where docID d = T.pack $ show $ valueAt "_id" d
raws d = do "table-raw" ## tableRawS d
"raw-id" ## textSplice $ docID d
I've been struggling for a few days now with no result. It is probably due to the lack of understanding compiled splices API. Please help!
EDIT
I did not provide enough details to my problem. The best approximation to the above interpreted variant that I managed to get is this:
tableBody = manyWithSplices runChildren tableRaw $ lift documents
tableRaw doc = do "table-raw" ## manyWithSplices runChildren rawCell $ lift labels
where rawCell label = "table-cell" ## pureSplice . textSplice $ at label doc
"table-rawid" ## pureSplice . textSplice $ at "_id" doc
where oid = T.pack . show. valueAt "_id"
It does not work! The problem is translating the raw rendering function which is tableRaw. So I will give more details.
The data I am feeding into the tableBody comes as a list of Map like structure:
document = ["_id" =: 12345, "name" =: "pretty", "model" =: "cool", "size" =: "big"]
So to pull the data out in a raw I need to map over list of labels
map (\l -> at l document) labels
I can do this with the interpreted varian without a problem. The interpreted example of tableRawS is parameterised by a ducument but maps over [labels]. I can not achieve this in compiled variant. I need both the document and the list of labels present in the tableRaw function so I can bind different cell-splices out of the document. This is real pain. I don't know how to do it. Whatever I do I end up with tableRaw mapping over document instead of mapping over list of labels.
Basically. I get [document] from the database with the above mentioned document structure, and I get labels from the database, where
labels = ["name", "model", "size"] -- table fields
I get data from the document with "at :: Label -> Value"
Having all that, how do I render this template:
<table class="table" data-title=${table-name}>
<thead>
<tr>
<th>#</th>
<table-head>
<th> <table-hcell/> </th>
</table-head>
</tr>
</thead>
<tbody>
<table-body>
<tr data-oid=${table-rowid}>
<td> <input type="checkbox"/> </td>
<table-raw>
<td> <table-rcell/> </td>
</table-raw>
</tr>
</table-body>
</tbody>

Suppose this is the structure that we want to render as a table:
data Table = Table
{
caption :: T.Text
, rows :: [[Int]]
}
A simple template could be something like
<body>
<mytable>
<table>
<caption><mycaptiontext/></caption>
<myrow>
<tr>
<mydata>
<td><mydatavalue/></td>
</mydata>
</tr>
</myrow>
</table>
</mytable>
</body>
Where mytable, mycaptiontext, myrow, mydata and mydatavalue are the tags that will be bound to splices. mytable in particular will be bound to a top-level splice.
There are three levels to consider: the table as a whole, the rows, and the data inside the rows. For each level, we are going to define a function which takes a runtime action and returns a compiled splice.
For the "row data" level, the runtime action carries the list of values in a row:
dataSplice :: Monad m => RuntimeSplice m [Int] -> C.Splice m
dataSplice = C.manyWithSplices C.runChildren splicefuncs
where
splicefuncs = do
"mydatavalue" ## (C.pureSplice . C.textSplice $ T.pack . show)
For the "rows" level, the runtime action carries the full list of rows:
rowSplice :: Monad m => RuntimeSplice m [[Int]] -> C.Splice m
rowSplice = C.manyWithSplices C.runChildren splicefuncs
where
splicefuncs = do
"mydata" ## dataSplice
Notice how we use dataSplice in the definition.
For the "whole table" level, the runtime action carries a Table:
tableSplice :: Monad m => RuntimeSplice m Table -> Splice m
tableSplice = C.withSplices C.runChildren splicefuncs
where
splicefuncs = do
"mycaptiontext" ## (C.pureSplice . C.textSplice $ caption)
"myrow" ## (rowSplice . liftM rows)
Notice how we use liftM here, transforming a RuntimeSplice m Table into a RuntimeSplice m [[Int]] so that the type fits with what rowSplice expects.
Now suppose we have a runtime action that produces the table data:
runtime :: Monad m => RuntimeSplice m Table
runtime = return $ Table "This is the caption" $
[ [3, 5, 6], [8, 3, 7 ] ]
(This one is trivial. A more complex action could fetch the data from a database, for example. Remember that, in Snap, RuntimeSplices have access to all the Snaplet machinery.)
We can combine tableSplice with runtime and register the result as a top-level splice in the Heist configuration, bound to the mytable tag. Like this:
let heistConfig = mempty {
hcCompiledSplices = do
"mytable" ## (tableSplice runtime)
.... other top-level splices here ...
}
This should work.
More examples of rendering nested structures with compiled Heist can be found in this tutorial.

Related

Why doesn't runConduit send all the data?

here's some xml i'm parsing:
<?xml version="1.0" encoding="utf-8"?>
<data>
<row ows_Document='Weekly Report 10.21.2020'
ows_Category='Weekly Report'/>
<row ows_Document='Daily Update 10.20.2020'
ows_Category='Daily Update'/>
<row ows_Document='Weekly Report 10.14.2020'
ows_Category='Weekly Report'/>
<row ows_Document='Weekly Report 10.07.2020'
ows_Category='Weekly Report'/>
<row ows_Document='Spanish: Reporte Semanal 07.10.2020'
ows_Category='Weekly Report'/>
</data>
i've been trying to figure out how to get the conduit parser to reject records unless ows_Category is Weekly Report and ows_Document doesn't contain Spanish. at first, i used a dummy value (in parseDoc' below) to filter them out after parsing, but then i realized i should be able to use Maybe (in the otherwise identical parseDoc below), together with join to collapse out my Maybe layer with the one used by tag' event parser that fails based on name or attribute matches. it compiles, but behaves bizarrely, apparently not even trying to send certain elements to the parser! how could this be?
{-# LANGUAGE OverloadedStrings #-}
import Conduit
import Control.Monad
import qualified Data.ByteString.Lazy.Char8 as L8
import Data.Foldable
import Data.String
import qualified Data.Text as T
import Data.XML.Types
import Text.XML.Stream.Parse
newtype Doc = Doc
{ name :: String
} deriving (Show)
main :: IO ()
main = do
r <- L8.readFile "oha.xml"
let doc = Doc . T.unpack
check (x,y) a b = if y == "Weekly Report" && not (T.isInfixOf "Spanish" x) then a else b
t :: (MonadThrow m, MonadIO m) => ((T.Text, T.Text) -> ConduitT Event o m c)
-> ConduitT Event o m (Maybe c)
t f = tag' "row" ((,) <$> requireAttr "ows_Document" <*> requireAttr "ows_Category") $ \x -> do
liftIO $ print x
f x
parseDoc, parseDoc' :: (MonadThrow m, MonadIO m) => ConduitT Event o m (Maybe Doc)
parseDoc = (join <$>) . t $ \z#(x,_) -> return $ check z (Just $ doc x) Nothing -- this version doesn't get sent all of the data! why!?!?
parseDoc' = t $ \z#(x,_) -> return $ doc $ check z x $ T.pack bad -- dummy value
parseDocs :: (MonadThrow m, MonadIO m) => ConduitT Event o m (Maybe Doc)
-> ConduitT Event o m [Doc]
parseDocs = f tagNoAttr "data" . many'
f g n = force (n <> " required") . g (fromString n)
go p = runConduit $ parseLBS def r .| parseDocs p
bad = "no good"
traverse_ print =<< go parseDoc
putStrLn ""
traverse_ print =<< filter ((/= bad) . name) <$> go parseDoc'
output -- notice how parseDoc isn't even sent one of the records (one that should succeed, from 10.14), while parseDoc' behaves as expected:
("Weekly Report 10.21.2020","Weekly Report")
("Daily Update 10.20.2020","Daily Update")
("Weekly Report 10.07.2020","Weekly Report")
("Spanish: Reporte Semanal 07.10.2020","Weekly Report")
Doc {name = "Weekly Report 10.21.2020"}
Doc {name = "Weekly Report 10.07.2020"}
("Weekly Report 10.21.2020","Weekly Report")
("Daily Update 10.20.2020","Daily Update")
("Weekly Report 10.14.2020","Weekly Report")
("Weekly Report 10.07.2020","Weekly Report")
("Spanish: Reporte Semanal 07.10.2020","Weekly Report")
Doc {name = "Weekly Report 10.21.2020"}
Doc {name = "Weekly Report 10.14.2020"}
Doc {name = "Weekly Report 10.07.2020"}
when i tried further simplifying by removing everything to do with ows_Category, suddenly parseDoc worked fine, establishing the soundness of the idea? when i instead removed everything to do with ows_Document, the problem remained.
i suspect i'm supposed to be doing this with requireAttrRaw, but i haven't been able to make sense of it and can't find doc/examples.
does this have to do with Applicative -- now that i think about it, it shouldn't be able to fail based on examining values, right?
UPDATES
i found this answer from the author for a previous version of the library, which includes the intriguing force "fail msg" $ return Nothing in a similar situation, but that abandons all parsing instead of just failing the current parse.
this comment suggests i need to throw an exception, and in the source, they use something like lift $ throwM $ XmlException "failed check" $ Just event, but like force ... return Nothing, this kills all parsing, instead of just the current parser. also i don't know how to get my hands on the event.
here's a merged pull request claiming to have addressed this issue, but it doesn't discuss how to use it, only that it is "trivial" :)
ANSWER
to be explicit about the answer:
parseAttributes :: AttrParser (T.Text, T.Text)
parseAttributes = do
d <- requireAttr "ows_Document"
c <- requireAttr "ows_Category"
ignoreAttrs
guard $ not (T.isInfixOf "Spanish" d) && c == "Weekly Report"
return d
parseDoc :: (MonadThrow m, MonadIO m) => ConduitT Event o m (Maybe Doc)
parseDoc = tag' "row" parseAttributes $ return . doc
or, since in this case the attribute values can be checked independently:
parseAttributes = requireAttrRaw' "ows_Document" (not . T.isInfixOf "Spanish")
<* requireAttrRaw' "ows_Category" ("Weekly Report" ==)
<* ignoreAttrs
where requireAttrRaw' n f = requireAttrRaw ("required attr value failed condition: " <> n) $ \(n',as) ->
asum $ (\(ContentText a) -> guard (n' == fromString n && f a) *> pure a) <$> as
but the latter leaves open these questions regarding requireAttrRaw:
shouldn't we need to know the namespace if we're in charge of verifying Name?
why does requireAttrRaw send us [Content] instead of two Maybe Content, one each for ContentText and ContentEntity?
what are we supposed to do with ContentEntity "For pass-through parsing"?
tl;dr In tag' "row" parseAttributes parseContent, the check function belongs to parseAttributes, not to parseContent.
Why it does not behave as expected
xml-conduit is (notably) designed around the following invariants:
when parsers are of type ConduitT Event o m (Maybe a), the Maybe layer encodes whether Events have been consumed
tag' parseName parseAttributes parseContent consumes Events if and only if both parseName and parseAttributes succeed
tag' parseName parseAttributes parseContent runs parseContent if and only if both parseName and parseAttributes succeed
In parseDoc:
the check function is called in the parseContent part; at this stage, tag' is already committed to consume Events, as per invariant 2
a stack of 2 Maybe layers are joined together:
the output of the check function, which encodes whether the current <row/> element is relevant
the "standard" Maybe layer from tag' signature, which encodes whether Events have been consumed, as per invariant 1
This essentially breaks invariant 1: when check returns Nothing, parseDoc returns Nothing despite consuming Events of the whole <row/> element.
This results in undefined behavior of all combinators of xml-conduit, notably many' (analyzed below.)
Why it behaves the way it does
The many' combinator relies on invariant 1 to do its job.
It is defined as many' consumer = manyIgnore consumer ignoreAnyTreeContent, that is:
try consumer
if consumer returns Nothing, then skip element or content using ignoreAnyTreeContent, assuming it hasn't been consumed yet by consumer, and recurse back to step (1)
In your case, consumer returns Nothing for the Daily Update 10.20.2020 item, even though the complete <row/> element has been consumed. Therefore, ignoreAnyTreeContent is run as a means to skip that particular <row/>, but actually ends up skipping the next one instead (Weekly Report 10.14.2020).
How to achieve the expected behavior
Move the check logic to the parseAttributes part, so that Event consumption becomes coupled to whether check passes.

Logical OR in HXT without duplicating results

I'm having a little trouble with HXT: I am trying to locate all the nodes in a document that match some criteria, and I'm trying to combine the lenses/XPaths as predicates in an OR-like fashion, using Control.Arrow.<+>, as this guide suggests. However, when I try to "run" the arrow on my document, I am getting duplicate results. Is there an easy way to remove the duplicates, or to combine the tests in a more meaningful way? Here is my code:
run :: App -> IO ()
run a = do
inputContents <- readFile (input a)
let doc = readString [withParseHTML yes, withWarnings no] inputContents
links <- runX . xshow $ doc >>> indentDoc //> cssLinks
mapM_ putStrLn links
cssLinks = links >>> (rels <+> hrefs <+> types)
where
links = hasName "link"
rels = hasAttrValue "rel" (isInfixOf "stylesheet")
hrefs = hasAttrValue "href" (endswith ".css")
types = hasAttrValue "type" (== "text/css")
Yet every time I run this (on any web page), I get duplicated results / nodes. I noticed that <+> is part of the ArrowPlus typeclass, which mimics a monoid, and ArrowXML is an instance of both ArrowList and ArrowTree, which gives me a lot to work with. Would I have to construct ArrowIf predicates? Any help with this would be wonderful :)
You may get the arrow result as a [XmlTree], then apply List.nub, then get the string rep.
import "hxt" Text.XML.HXT.DOM.ShowXml as SX
...
links <- runX $ doc >>> indentDoc //> cssLinks
-- first remove duplicates (List.nub) then apply SX.xshow
putStrLn (SX.xshow . L.nub $ links)

Snap: compiled splices code example

I think I did asked a similar question some time ago but it was not answered due to unstable API. So I was waiting for the 0.13 to pass by. I am not sure if it is correct to bring up a similar question...?
What is the alternative to interpreted runChildrenWith(Text) and mapSplices in the compiled splices world? (this combination seems to be the most common)
I would really appreciate some code examples if possible.
If I understand correctly, we get together all the application splices and then add them to the heistInit. Can anyone show how to do it please?
Does the splice binding tag has to be unique across the whole application?
Is there a completed snap project utilising new APIs and compiled splices so that I could read and see learn?
Thank you.
-- UPDATE --
Great answer below. But some parts (the ones with lenses) got me even more confused, unfortunately.
If I understand correctly this is the simple way to splice a string:
mySplice = "testSplice" ## testSplice
where testSplice = return $ C.yieldRuntimeText $ do
return "text to be spliced"
If i need to run the spliced string several times, say in 5 table raws i would do it like this:
mySplices = C.manyWithSplices C.runChildren mySplice
Is this correct?
I get bunch of errors trying to add the splices in heist config.
addConfig h $ mempty
{
hcCompiledSplices = "mySplice" ## mySplice -- or mySplices
}
Where am I going wrong? Sorry for being slow.
All I need really ( just for now so I can understand) is to splice and display a simple string that I receive from database.
-- UPDATE 2 --
Thanks to the extremle helpfull Daniel`s answer I can finally get something working.
So far I get both variants of code working.
The first one, thanks to Daniel
stringSplice :: Monad n => C.Splice n
stringSplice = C.manyWithSplices C.runChildren splicefuncs (return ["aa","bb","cc"])
where
splicefuncs = "string" ## (C.pureSplice . C.textSplice $ id)
And the secod
testSplice :: C.Splice (Handler App App)
testSplice = return $ C.yieldRuntimeText $ return "text to be spliced"
Where
(C.pureSplice . C.textSplice $ id)
produces similar results to
return $ C.yieldRuntimeText $ return "text to be spliced"
Is there difference between the above? Any cases that one would prefer one to another? They seem to produce the same results.
There is a "deferMany" function in the compiled splices lib that, according to the docs, produces similar results to the mapSplices in interpreted lib.
Can we use it instead of "C.manyWithSplices C.runChildren" combination??
Let's say you want to display information about a list of persons using compiled splices (assume that we start from the scaffolding generated by snap init.)
A very simple _persons.tpl template with dummy values would be something like
<body>
<person>
<div>
<h1><name>dummy name</name></h1>
<p><age>77</age></p>
<p><location>jauja</location></p>
</div>
</person>
</body>
Where person, name, age, and location are the tags to be spliced.
We define a trivial Snaplet that holds the info
data Foo = Foo
{
_persons :: [Person]
}
makeLenses ''Foo
data Person = Person
{
_name :: Text
, _age :: Int
, _location :: Text
}
makeLenses ''Person
and we add it to the App record:
data App = App
{ _heist :: Snaplet (Heist App)
, _sess :: Snaplet SessionManager
, _auth :: Snaplet (AuthManager App)
, _foo :: Snaplet Foo
}
we add the following to the app initializer
f <- nestSnaplet "foo" foo $ makeSnaplet "foo" "Foo Snaplet" Nothing $ return $ Foo $
[ Person "Ricardo" 33 "Los Cantones"
, Person "Luis" 38 "Montealto"
]
...
return $ App h s a f
This function constructs a Handler that returns the list of persons (using view from Control.Lens):
personH :: SnapletLens b Foo -> Handler b b [Person]
personH l = withTop l $ view persons <$> get
This function constructs the appropiate compiled splice from a RuntimeSplice that produces a list of Persons. RuntimeSplices represent information that can only be known at run time, as opposed to load time:
personSplice :: Monad n => RuntimeSplice n [Person] -> C.Splice n
personSplice = C.manyWithSplices C.runChildren splicefuncs
where
splicefuncs = mconcat
[ "name" ## (C.pureSplice . C.textSplice $ view name)
, "age" ## (C.pureSplice . C.textSplice $ T.pack . show . view age)
, "location" ## (C.pureSplice . C.textSplice $ view location)
]
And this function can be used to register the splice in the global Heist configuration. Notice that we lift the Handler into a RuntimeSplice:
addPersonSplices :: HasHeist b => Snaplet (Heist b) ->
SnapletLens b Foo ->
Initializer b v ()
addPersonSplices h l = addConfig h $ mempty
{
hcCompiledSplices = "person" ## (personSplice . lift $ personH l)
}
Be sure to add this line to the app initializer:
addPersonSplices h foo
And to add the following pair to the app's routes:
("/persons", cRender "_persons")
If you now run the server, navigating to http://127.0.0.1:8000/persons should show the list.
UPDATE
For the simpler case (no complex records, no lenses) in which you only want to show a list of strings.
The template could be something like:
<body>
<strings>
<p><string>dummy value</string></p>
</strings>
</body>
The top-level splice would be:
stringSplice :: Monad n => C.Splice n
stringSplice = C.manyWithSplices C.runChildren splicefuncs (return ["aa","bb","cc"])
where
splicefuncs = "string" ## (C.pureSplice . C.textSplice $ id)
This means "when we encounter the tag associated to this splice, perform an action that produces a list of strings, and for each string, render the contents of the tag, substituting the current string for the string tag".
Notice that the signature of manyWithSplices forces the stuff to the right of the (##) to have type RuntimeSplice n Text -> Splice n. Here id has type Text -> Text. C.TextSplice transforms it into something of type Text -> Builder, and C.pureSplice performs the final transformation into a RuntimeSplice n Text -> Splice n.
In place of (return ["aa","bb","cc"]) you could provide a more complex action that connected a database and extracted the strings form there.
A function to register this splice would be:
addStringSplices :: HasHeist b => Snaplet (Heist b) -> Initializer b v ()
addStringSplices h = addConfig h $ mempty
{
hcCompiledSplices = "strings" ## stringSplice
}

Haskell Snap Framework - Dynamic hyperlinks with Heist

I am trying to create dynamic links using the Heist templating system. The problem is that the links are appearing as text rather than being interpreted as html. Is there a specific method to create dyamic lists like this with Heist?
The function where the link is constructed:
renderCategories :: Monad m => Db.Category -> I.Splice m
renderCategories (Db.Category catid catname catdesc) =
I.runChildrenWithText [ ("categoryId", T.concat $ ["<a href='http://localhost:8000/thread_home?cateid=", T.pack . show $ catid, "'>", T.pack . show $ catid, "</a>"])
, ("categoryName", catname)
, ("categoryDesc", catdesc)]
The tag appears as "http://localhost:8000/thread_home?cateid=1'>1" text on the webpage. And the source shows it as follows:
<a href='http://localhost:8000/thread_home?cateid=1'>1</a>
I figure that I need to have it print the actual < and > but I am not sure how to achieve this.
As I am currently running runChildrenWithText to populate this Heist template changing to just runChildrenWith requires splices instead of text and so instead of attempting this I am hoping there is some way to runChildrenWithText without the '<' and '>' being converted to '&lt' and '&gt'.
Any help is appreciated!
EDIT
I am trying to manually create the link using:
renderCategories :: Monad m => Db.Category -> I.Splice m
renderCategories (Db.Category catid catname catdesc) =
I.runChildrenWith [ ("categoryId", return $ X.Element "a"[("href", "http://localhost")] $ X.TextNode (T.pack $ show catid))]
However I am encountering two errors:
Couldn't match type `X.Node' with `[X.Node]'
Expected type: I.Splice m
Actual type: heist-0.11.1:Heist.Types.HeistT m m X.Node
In the expression:
return
$ X.Element "a" [("href", "http://localhost")]
$ X.TextNode (T.pack $ show catid)
and
Couldn't match expected type `[X.Node]' with actual type `X.Node'
In the return type of a call of `X.TextNode'
In the second argument of `($)', namely
`X.TextNode (T.pack $ show catid)'
I do not really understand these errors at the moment and any help is appreciated.
Working function for both returning the link and normal text:
renderCategories :: Monad m => Db.Category -> I.Splice m
renderCategories (Db.Category catid catname catdesc) =
I.runChildrenWith [( "categoryId", return $ [X.Element "a" [("href", T.concat $ ["http://localhost:8000/thread_home?cateid=", T.pack $ show catid] )] [X.TextNode (T.pack $ show catid)] ] )
, ("categoryName", I.textSplice catname)
, ("categoryDesc", I.textSplice catdesc)]
The behavior you are seeing is exactly what is intended. The reason you are having problems is because you're using runChildrenWithText which is a higher level function designed for situations where you are returning text nodes. It is meant for when you want that actual text on your page. What you are seeing is the correct way to achieve that.
A splice is a computation that returns a list of nodes.
type Splice n = HeistT n n [Node]
Node is a representation of the DOM as Haskell types, so if you want to return a link, you should do something like this:
return $ [Element "a" [("href", "http://localhost")] [TextNode (T.pack $ show catid)]]
To use this kind of a splice, you'll need to use runChildrenWith instead of runChildrenWithText.
If this manual creation of Nodes seems ugly to you, there's also a more convenient option. If you import the module Text.Blaze.Renderer.XmlHtml, you'll find functions there that let you generate Node trees using blaze-html syntax.

put xml into a hash table

I am trying to get the informations out of a xml file into a lookup table.
So far I have been reading what librairies might be available and how to use them.
I went with hxt and hashtables.
Here is the file :
<?xml version="1.0" encoding="UTF-8" ?>
<tables>
<table name="nametest1">
test1
</table>
<table name="nametest2">
test2
</table>
</tables>
I would like to have the following pairs:
nametest1, test1
nametest2, test2
etc...
-- | We get the xml into a hash
getTables :: IO (H.HashTable String String)
getTables = do
confPath <- getEnv "ENCODINGS_XML_PATH"
doc <- runX $ readDocument [withValidate no] confPath
-- this is the part I don't have
-- I get the whole hashtable create and insert process
-- It is the get the xml info that is blocking
where -- I think I might use the following so I shamelessly took them from the net
atTag tag = deep (isElem >>> hasName tag)
text = getChildren >>> getText
I saw many examples of how to do similar things but I can't figure out how to get the name attribute at each node.
Cheers,
rakwatt
Here is an example that reads a file with the name of test.xml and just prints out the (name,text) pairs:
import Text.XML.HXT.Core
-- | Gets the name attribute and the content of the selected items as a pair
getAttrAndText :: (ArrowXml a) => a XmlTree (String, String)
getAttrAndText =
getAttrValue "name" -- And zip it together with the the attribute name
&&& deep getText -- Get the text of the node
-- | Gets all "table" items under a root tables item
getTableItem :: (ArrowXml a) => a XmlTree XmlTree
getTableItem =
deep (hasName "tables") -- Find a tag <tables> anywhere in the document
>>> getChildren -- Get all children of that tag
>>> hasName "table" -- Filter those that have the tag <table>
>>> hasAttr "name" -- Filter those that have an attribute name
-- | The main function
main = (print =<<) $ runX $ -- Print the result
readDocument [withValidate no] "test.xml" -- Read the document
>>> getTableItem -- Get all table items
>>> getAttrAndText -- Get the attribute 'name' and the text of those nodes
The construction of the pairs happens in getAttrAndText. The rest of the functions just open the file and select all tags that are an immediate children of a tag. You still might want to strip leading whitespace in the text.

Resources