module LWN.Page where import Text.Pandoc import Data.Time (getCurrentTime) import System.IO (Handle) import qualified Data.ByteString.Lazy as B (ByteString, hPut) import Data.String.Utils (split, strip) import Data.Maybe (catMaybes, fromJust, isNothing) import Data.Tree.NTree.TypeDefs (NTree) import Test.HUnit (Assertion, assertEqual) import Test.Framework (Test, testGroup) import Test.Framework.Providers.HUnit (testCase) import Text.XML.HXT.Core ( ArrowXml, IOSArrow, XmlTree, XNode, (>>>), (/>), (//>), getChildren, getText, hasAttrValue, hasName, mkName, none, processAttrl, processTopDown, runX, setElemName, xshow, when ) import Text.HandsomeSoup (css, parseHtml) import LWN.Article import XHTML data Page = -- | An LWN page with one article on it. ArticlePage { article :: Article } | -- | An LWN page with more than one article on it. These require -- different parsing and display functions than the single-article -- pages. FullPage { headline :: String, articles :: [Article] } instance XHTML Page where to_xhtml (ArticlePage a) = "" ++ "" ++ "" ++ " " ++ " " ++ (show $ LWN.Article.title a) ++ "" ++ "" ++ "" ++ "
" ++ (to_xhtml a) ++ "
" ++ "" ++ "" to_xhtml (FullPage hl as) = "" ++ "" ++ "" ++ " " ++ " " ++ hl ++ "" ++ "" ++ "" ++ "
" ++ "

" ++ hl ++ "

" ++ (concatMap to_xhtml as) ++ "
" ++ "" ++ "" remove_images :: (ArrowXml a) => a XmlTree XmlTree remove_images = processTopDown ((none) `when` is_image) is_link :: (ArrowXml a) => a XmlTree XmlTree is_link = hasName "a" replace_links_with_spans :: (ArrowXml a) => a XmlTree XmlTree replace_links_with_spans = processTopDown $ (make_span >>> remove_attrs) `when` is_link where make_span = setElemName $ mkName "span" remove_attrs = processAttrl none -- | Preprocessing common to both page types. preprocess :: IOSArrow XmlTree (NTree XNode) -> IOSArrow XmlTree (NTree XNode) preprocess xml = xml >>> remove_images >>> replace_links_with_spans parse :: IOSArrow XmlTree (NTree XNode) -> IO (Maybe Page) parse xml = do let clean_xml = preprocess xml appr <- ap_parse clean_xml fppr <- fp_parse clean_xml return $ if (isNothing appr) then fppr else appr parse_headline :: IOSArrow XmlTree (NTree XNode) -> IO (Maybe String) parse_headline xml = do let element_filter = xml >>> css "div.PageHeadline h1" let element_text_filter = element_filter /> getText element_text <- runX element_text_filter return $ case element_text of [x] -> Just $ strip x [] -> Nothing _ -> error "Found more than one headline." parse_byline :: IOSArrow XmlTree (NTree XNode) -> IO (Maybe String) parse_byline xml = do let element_filter = xml >>> css "div.FeatureByLine" let element_text_filter = element_filter /> getText element_text <- runX element_text_filter return $ case element_text of [x] -> Just $ strip x [] -> Nothing _ -> error "Found more than one article byline." -- -- ArticlePage Stuff -- ap_parse :: IOSArrow XmlTree (NTree XNode) -> IO (Maybe Page) ap_parse xml = do arts <- ap_parse_articles xml case arts of Just [x] -> return $ Just $ ArticlePage x _ -> return Nothing ap_parse_body :: IOSArrow XmlTree (NTree XNode) -> IO (Maybe String) ap_parse_body xml = do let element_filter = xml >>> css "div.ArticleText" let element_html_filter = xshow element_filter element_html <- runX element_html_filter return $ case element_html of [x] -> Just x [] -> Nothing _ -> error "Found more than one article." ap_parse_articles :: IOSArrow XmlTree (NTree XNode) -> IO (Maybe [Article]) ap_parse_articles xml = do parsed_headline <- parse_headline xml parsed_byline <- parse_byline xml parsed_body <- ap_parse_body xml let title' = Title (fromJust parsed_headline) let byline' = Byline parsed_byline let body' = BodyHtml (fromJust parsed_body) return $ Just $ [Article title' byline' body'] -- -- FullPage Stuff -- fp_parse :: IOSArrow XmlTree (NTree XNode) -> IO (Maybe Page) fp_parse xml = do hl <- parse_headline xml parsed_articles <- fp_parse_articles xml case parsed_articles of them@(_:_) -> return $ Just $ FullPage (fromJust hl) them _ -> return Nothing fp_parse_article_title :: IOSArrow XmlTree (NTree XNode) -> IO (Maybe String) fp_parse_article_title xml = do let element_filter = xml >>> css "h2.SummaryHL" let element_text_filter = element_filter //> getText element_text <- runX element_text_filter return $ case element_text of [x] -> Just $ strip x [] -> Nothing _ -> error "Found more than one article title." is_title :: (ArrowXml a) => a XmlTree XmlTree is_title = (hasName "h2") >>> (hasAttrValue "class" (== "SummaryHL")) is_byline :: (ArrowXml a) => a XmlTree XmlTree is_byline = (hasName "div") >>> (hasAttrValue "class" (== "FeatureByLine")) is_image :: (ArrowXml a) => a XmlTree XmlTree is_image = hasName "img" remove_title :: (ArrowXml a) => a XmlTree XmlTree remove_title = processTopDown ((none) `when` is_title) remove_byline :: (ArrowXml a) => a XmlTree XmlTree remove_byline = processTopDown ((none) `when` is_byline) fp_parse_article_body :: IOSArrow XmlTree (NTree XNode) -> IO (Maybe String) fp_parse_article_body xml = do -- First, delete the article title and byline. let clean_xml' = xml >>> remove_title >>> remove_byline -- The only child of the body element should be a div.lwn-article -- since we wrapped the article's HTML in that. let clean_xml = clean_xml' >>> css "body" >>> getChildren clean_html <- runX . xshow $ clean_xml return $ case clean_html of [x] -> Just x [] -> Nothing _ -> error "Found more than one article body." fp_parse_article :: IOSArrow XmlTree (NTree XNode) -> IO (Maybe Article) fp_parse_article xml = do parsed_article_title <- fp_parse_article_title xml parsed_article_byline <- parse_byline xml parsed_article_body <- fp_parse_article_body xml let title' = Title $ fromJust parsed_article_title let byline' = Byline parsed_article_byline let body' = BodyHtml $ fromJust parsed_article_body return $ Just $ Article title' byline' body' parse_html_article :: String -> IO (Maybe Article) parse_html_article html = do let xml = parseHtml $ wrap_in_body_div html fp_parse_article xml -- | In the full page, all of the article titles and bodies are -- wrapped in one big div.ArticleText. parse_bodies :: IOSArrow XmlTree (NTree XNode) -> IOSArrow XmlTree (NTree XNode) parse_bodies xml = xml >>> css "div.ArticleText" fp_parse_articles :: IOSArrow XmlTree (NTree XNode) -> IO [Article] fp_parse_articles xml = do bodies <- runX . xshow $ parse_bodies xml let article_separator = "

" let split_articles'' = split article_separator (concat bodies) -- The first element will contain the crap before the first . let split_articles' = tail split_articles'' -- Put the separator back, it was lost during the split. let split_articles = map (article_separator ++) split_articles' --_ <- mapM print_article split_articles real_articles <- mapM parse_html_article split_articles let just_articles = catMaybes real_articles return just_articles -- | This makes it easy to select otherwise-random chunks of html -- using 'css'. wrap_in_body_div :: String -> String wrap_in_body_div s = "
" ++ s ++ "
" -- -- Epublishable stuff -- title :: Page -> String title (ArticlePage a) = getTitle $ LWN.Article.title a title (FullPage hl _) = hl metadata :: Page -> IO String metadata obj = do date <- getCurrentTime return $ "http://lwn.net/\n" ++ "" ++ (show date) ++ "\n" ++ "en-US\n" ++ "Copyright Eklektix, Inc.\n" ++ "" ++ (LWN.Page.title obj) ++ "\n" epublish :: Page -> Handle -> IO () epublish obj handle = do let xhtml = to_xhtml obj epmd <- metadata obj epub <- xhtml_to_epub epmd xhtml B.hPut handle epub xhtml_to_epub :: String -> String -> IO B.ByteString xhtml_to_epub epmd = write_epub . read_html where my_writer_options = defaultWriterOptions { writerEPUBMetadata = epmd } write_epub = writeEPUB Nothing [] my_writer_options read_html = readHtml defaultParserState -- -- Tests -- test_preprocess_links :: Assertion test_preprocess_links = do actual_xml' <- runX $ (preprocess input_xml) >>> css "body" let actual_xml = actual_xml' !! 0 expected_xml' <- runX $ expected_xml'' >>> css "body" let expected_xml = expected_xml' !! 0 assertEqual "Links are replaced with spans" expected_xml actual_xml where input_html = "Hello, world!" input_xml = parseHtml input_html expected_html = "Hello, world!" expected_xml'' = parseHtml expected_html page_tests :: Test page_tests = testGroup "Page Tests" [ testCase "Links are replaced with spans" test_preprocess_links ]