{-# LANGUAGE OverloadedStrings #-} module Queries where import Control.Applicative -- base import Control.Lens -- lens import Data.Text (Text) -- text import Text.Xml.Lens -- xml-html-conduit-lens -- $setup -- >>> :set -XOverloadedStrings -- >>> import Text.Xml.Lens -- >>> import qualified Data.Text.Lazy.IO as Text -- >>> doc <- Text.readFile "example/books.xml" -- | List titles of the books in "Textbooks" category: -- -- >>> doc ^.. listTitles -- ["Learn You a Haskell for Great Good!","Programming in Haskell","Real World Haskell"] listTitles :: AsXmlDocument t => Traversal' t Text listTitles = xml...attributed (ix "category".only "Textbooks").node "title".text -- | List authors of the books longer then 500 pages: -- -- >>> doc ^.. listAuthors -- ["Bryan O'Sullivan, Don Stewart, and John Goerzen","Benjamin C. Pierce"] listAuthors :: AsXmlDocument t => Traversal' t Text listAuthors = xml...filtered (has (node "pages".text.filtered (> "500"))).node "author".text -- | List titles and authors of the books in "Textbooks" category -- -- >>> doc ^.. listTitlesAndAuthors -- [("Learn You a Haskell for Great Good!","Miran Lipovaca"),("Programming in Haskell","Graham Hutton"),("Real World Haskell","Bryan O'Sullivan, Don Stewart, and John Goerzen")] listTitlesAndAuthors :: AsXmlDocument t => Fold t (Text, Text) listTitlesAndAuthors = xml...attributed (ix "category".only "Textbooks") .runFold (liftA2 (,) (Fold (node "title".text)) (Fold (node "author".text))) -- | Lists the title of the third book in the list -- -- >>> doc ^? listThirdTitle -- Just "Programming in Haskell" listThirdTitle :: AsXmlDocument t => Fold t Text listThirdTitle = xml.parts.ix 2.node "title".text -- | List all tags from top to bottom: -- -- >>> doc ^.. listAllTags -- ["books","book","title","author","pages","price","book","title","author","pages","book","title","author","pages","book","title","author","pages","book","title","author","pages","book","title","author","pages","book","title","author"] listAllTags :: AsXmlDocument t => Fold t Text listAllTags = xml.folding universe.name -- | Compute the length of the books list: -- -- >>> doc & countBooks -- 7 countBooks :: AsXmlDocument t => t -> Int countBooks = lengthOf (xml.plate) -- | Find the title of the first book in "Joke" category: -- -- >>> doc ^? titleOfFirstJokeBook -- Just "Functional Ikamusume" titleOfFirstJokeBook :: AsXmlDocument t => Traversal' t Text titleOfFirstJokeBook = xml...attributed (ix "category".only "Joke").node "title".text -- | Append the string " pages" to each `` tag contents: -- -- >>> doc & appendPages & Text.putStr -- -- -- Haskell 98 language and libraries: the Revised Report -- Simon Peyton Jones -- 272 pages -- £45.00 -- -- -- Learn You a Haskell for Great Good! -- Miran Lipovaca -- 360 pages -- -- -- Programming in Haskell -- Graham Hutton -- 200 pages -- -- -- Real World Haskell -- Bryan O'Sullivan, Don Stewart, and John Goerzen -- 700 pages -- -- -- The Fun of Programming -- Jeremy Gibbons and Oege de Moor -- 288 pages -- -- -- Types and Programming Languages -- Benjamin C. Pierce -- 645 pages -- -- -- Functional Ikamusume -- Team "Referential Transparent Sea Keepers" -- -- appendPages :: AsXmlDocument t => t -> t appendPages = xml...node "pages".text <>~ " pages"