{-# OPTIONS_GHC -fth #-} module Main where import XTree import XQueryParser import XQueryCompiler import XMLParse(parseDocument) import IO main = do let [XText f_0] = [XText "data/dblp.xml"] doc_1 <- readFile f_0 res <- (\_doc0 -> return (foldr (\x_2 -> (\x -> \r_3 -> foldir (\x_4 i_5 r_6 -> if case [trueXT | x_7 <- text (foldr (\a_8 s_9 -> child_step "author" a_8 ++ s_9) [] (x :: XSeq)), y_10 <- text [XText "David Maier"], compareXTrees x_7 y_10 == EQ] of [XInt k_11] -> k_11 == i_5 b_12 -> conditionTest b_12 then x_4 : r_6 else r_6) [] [XElem "paper" [] 0 ((text (foldr (\a_13 s_14 -> child_step "booktitle" a_13 ++ s_14) [] (x :: XSeq)) ++ [XText ": "]) ++ text (foldr (\a_15 s_16 -> child_step "title" a_15 ++ s_16) [] (x :: XSeq)))] 1 ++ r_3) [x_2]) [] (foldr (\a_17 s_18 -> descendant_step "inproceedings" a_17 ++ s_18) [] [_doc0]))) (materialize (parseDocument doc_1)) putXSeq res