]> gitweb.michael.orlitzky.com - dead/lwn-epub.git/blobdiff - src/LWN/Page.hs
Move the pure-xml functions into the LWN.XHTML module.
[dead/lwn-epub.git] / src / LWN / Page.hs
index 0307214176a82c469f1f555a056b553c05bd3b06..97171c641be08a6761a1a1800002190c7f10b9ed 100644 (file)
@@ -3,66 +3,58 @@
 module LWN.Page
 where
 
-import qualified Data.Map as Map
+import qualified Data.Map as Map (lookup)
 import Data.Time (getCurrentTime)
-import System.IO (Handle)
 import qualified Data.ByteString.Lazy as B (ByteString, hPut)
-import Data.List (isInfixOf)
 import Data.String.Utils (split, strip)
 import Data.Maybe (catMaybes, fromJust, isNothing)
-import Data.Tree.NTree.TypeDefs (NTree)
+import Prelude hiding (readFile)
+import System.IO (Handle, hClose, hFlush)
 import Test.HUnit (Assertion, assertEqual)
 import Test.Framework (Test, testGroup)
 import Test.Framework.Providers.HUnit (testCase)
-import Text.Pandoc
+import Text.Pandoc (
+  defaultParserState,
+  defaultWriterOptions,
+  readHtml,
+  writeEPUB,
+  writerEPUBMetadata)
 import Text.XML.HXT.Core (
   ArrowXml,
   IOSArrow,
   XmlTree,
-  XNode,
   (>>>),
   (/>),
   (//>),
   changeAttrValue,
-  getAttrValue,
   getChildren,
   getText,
-  hasAttrValue,
   hasName,
-  isElem,
-  mkName,
-  none,
   processAttrl,
   processTopDown,
   runX,
-  setElemName,
   xshow,
-  when
-  )
+  when)
 import Text.HandsomeSoup (css, parseHtml)
 
+import Configuration (Cfg)
 import LWN.Article
-import LWN.HTTP (save_image)
-import LWN.URI (URL, try_make_absolute_url)
-import XHTML
+import LWN.HTTP (
+  ImageMap,
+  download_image_urls,
+  get_article_contents)
+import LWN.URI (URL)
+import LWN.XHTML (
+  XHTML,
+  image_srcs,
+  is_image,
+  preprocess,
+  remove_byline,
+  remove_title,
+  to_xhtml,
+  xml_from_contents)
 
--- Map absolute image URLs to local system file paths where the image
--- referenced by the URL is stored.
-type ImageMap = Map.Map URL FilePath
 
--- Should be called *after* preprocessing.
-download_images :: IOSArrow XmlTree (NTree XNode) -> IO ImageMap
-download_images xml = do
-  image_urls <- runX $ xml >>> image_srcs
-  files <- mapM save_image image_urls
-  let pairs = zip image_urls files
-  return $ foldl my_insert empty_map pairs
-  where
-    empty_map = Map.empty :: ImageMap
-
-    my_insert :: ImageMap -> (URL, Maybe FilePath) -> ImageMap
-    my_insert dict (_, Nothing)  = dict
-    my_insert dict (k, Just v) = Map.insert k v dict
 
 
 data Page =
@@ -87,9 +79,7 @@ instance XHTML Page where
     "  <title>" ++ (show $ LWN.Article.title a) ++ "</title>" ++
     "</head>" ++
     "<body>" ++
-    "<div>" ++
     (to_xhtml a) ++
-    "</div>" ++
     "</body>" ++
     "</html>"
 
@@ -112,39 +102,21 @@ instance XHTML Page where
 
 
 
-is_link :: (ArrowXml a) => a XmlTree XmlTree
-is_link =
-  isElem >>> hasName "a"
-
-
-remove_comment_links  :: (ArrowXml a) => a XmlTree XmlTree
-remove_comment_links =
-  processTopDown $ kill_comments `when` is_link
-  where    
-    contains = isInfixOf
-
-    is_comment_link =
-      hasAttrValue "href" (contains "#Comments")
+page_from_url :: Cfg -> URL -> IO (Maybe Page)
+page_from_url cfg url = do
+  contents <- get_article_contents cfg url  
+  case (xml_from_contents contents) of
+    Just html -> parse html
+    Nothing -> return Nothing
 
-    kill_comments =
-      none `when` is_comment_link
 
-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
 
+-- Should be called *after* preprocessing.
+download_images :: IOSArrow XmlTree XmlTree -> IO ImageMap
+download_images xml = do
+  image_urls <- runX $ xml >>> image_srcs
+  download_image_urls image_urls
 
--- | Preprocessing common to both page types.
-preprocess :: (ArrowXml a) => a XmlTree XmlTree
-preprocess =
-  make_image_srcs_absolute
-  >>>
-  remove_comment_links
-  >>>
-  replace_links_with_spans
 
 
 replace_remote_img_srcs :: (ArrowXml a) => ImageMap -> a XmlTree XmlTree
@@ -168,7 +140,7 @@ replace_remote_img_srcs image_map =
       processAttrl $ (change_src `when` (hasName "src"))
 
 
-parse :: IOSArrow XmlTree (NTree XNode) -> IO (Maybe Page)
+parse :: IOSArrow XmlTree XmlTree -> IO (Maybe Page)
 parse xml = do
   let clean_xml = xml >>> preprocess
   image_map <- download_images clean_xml
@@ -178,12 +150,12 @@ parse xml = do
   return $
     if (isNothing appr) then
       fppr
-    else 
+    else
       appr
 
 
 
-parse_headline :: IOSArrow XmlTree (NTree XNode) -> IO (Maybe String)
+parse_headline :: IOSArrow XmlTree XmlTree -> IO (Maybe String)
 parse_headline xml = do
   let element_filter = xml >>> css "div.PageHeadline h1"
   let element_text_filter = element_filter /> getText
@@ -195,7 +167,7 @@ parse_headline xml = do
       _   -> error "Found more than one headline."
 
 
-parse_byline :: IOSArrow XmlTree (NTree XNode) -> IO (Maybe String)
+parse_byline :: IOSArrow XmlTree XmlTree -> IO (Maybe String)
 parse_byline xml = do
   let element_filter = xml >>> css "div.FeatureByLine"
   let element_text_filter = element_filter /> getText
@@ -210,15 +182,15 @@ parse_byline xml = do
 --
 -- ArticlePage Stuff
 --
-ap_parse :: IOSArrow XmlTree (NTree XNode) -> IO (Maybe Page)
+ap_parse :: IOSArrow XmlTree XmlTree -> IO (Maybe Page)
 ap_parse xml = do
-    arts <- ap_parse_articles xml          
+    arts <- ap_parse_articles xml
     case arts of
       [x] -> return $ Just $ ArticlePage x
       _   -> return Nothing
 
-  
-ap_parse_body :: IOSArrow XmlTree (NTree XNode) -> IO (Maybe String)
+
+ap_parse_body :: IOSArrow XmlTree XmlTree -> IO (Maybe String)
 ap_parse_body xml = do
   let element_filter = xml >>> css "div.ArticleText"
   let element_html_filter = xshow element_filter
@@ -229,7 +201,7 @@ ap_parse_body xml = do
             _   -> error "Found more than one article."
 
 
-ap_parse_articles :: IOSArrow XmlTree (NTree XNode) -> IO [Article]
+ap_parse_articles :: IOSArrow XmlTree XmlTree -> IO [Article]
 ap_parse_articles xml = do
   parsed_headline <- parse_headline xml
   parsed_byline   <- parse_byline xml
@@ -239,11 +211,11 @@ ap_parse_articles xml = do
 
   if (isNothing parsed_headline) || (isNothing parsed_body)
   then return []
-  else do    
+  else do
     let title'  = Title    $ fromJust parsed_headline
     let byline' = Byline     parsed_byline
     let body'   = BodyHtml $ fromJust parsed_body
-    
+
     return $ [Article title' byline' body']
 
 
@@ -252,7 +224,7 @@ ap_parse_articles xml = do
 -- FullPage Stuff
 --
 
-fp_parse :: IOSArrow XmlTree (NTree XNode) -> IO (Maybe Page)
+fp_parse :: IOSArrow XmlTree XmlTree -> IO (Maybe Page)
 fp_parse xml = do
     hl <- parse_headline xml
     parsed_articles <- fp_parse_articles xml
@@ -262,7 +234,7 @@ fp_parse xml = do
 
 
 
-fp_parse_article_title :: IOSArrow XmlTree (NTree XNode) -> IO (Maybe String)
+fp_parse_article_title :: IOSArrow XmlTree XmlTree -> IO (Maybe String)
 fp_parse_article_title xml = do
   let element_filter = xml >>> css "h2.SummaryHL"
   let element_text_filter = element_filter //> getText
@@ -274,35 +246,8 @@ fp_parse_article_title xml = do
 
 
 
-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 = isElem >>> 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 :: IOSArrow XmlTree XmlTree -> IO (Maybe String)
 fp_parse_article_body xml = do
   -- First, delete the article title and byline.
   let clean_xml' = xml >>> remove_title >>> remove_byline
@@ -315,7 +260,7 @@ fp_parse_article_body xml = do
             []  -> Nothing
             _   -> error "Found more than one article body."
 
-fp_parse_article :: IOSArrow XmlTree (NTree XNode) -> IO (Maybe Article)
+fp_parse_article :: IOSArrow XmlTree XmlTree -> IO (Maybe Article)
 fp_parse_article xml = do
   parsed_article_title    <- fp_parse_article_title xml
   parsed_article_byline   <- parse_byline xml
@@ -335,15 +280,15 @@ 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 :: IOSArrow XmlTree XmlTree -> IOSArrow XmlTree XmlTree
 parse_bodies xml =
   xml >>> css "div.ArticleText"
 
 
-fp_parse_articles :: IOSArrow XmlTree (NTree XNode) -> IO [Article]
+fp_parse_articles :: IOSArrow XmlTree XmlTree -> IO [Article]
 fp_parse_articles xml = do
   bodies <- runX . xshow $ parse_bodies xml
   let article_separator = "<h2 class=\"SummaryHL\">"
@@ -395,7 +340,8 @@ epublish obj handle = do
   epmd <- metadata obj
   epub <- xhtml_to_epub epmd xhtml
   B.hPut handle epub
-
+  hFlush handle
+  hClose handle
 
 xhtml_to_epub :: String -> String -> IO B.ByteString
 xhtml_to_epub epmd =
@@ -406,30 +352,6 @@ xhtml_to_epub epmd =
      read_html  = readHtml defaultParserState
 
 
-
---
--- Misc
---
-
-image_srcs :: (ArrowXml a) => a XmlTree URL
-image_srcs =
-  css "img"
-  >>>
-  getAttrValue "src"
-
-make_image_srcs_absolute :: (ArrowXml a) => a XmlTree XmlTree
-make_image_srcs_absolute =
-  processTopDown (make_srcs_absolute `when` is_image)
-  where
-    change_src :: (ArrowXml a) => a XmlTree XmlTree
-    change_src =
-      changeAttrValue try_make_absolute_url
-
-    make_srcs_absolute :: (ArrowXml a) => a XmlTree XmlTree
-    make_srcs_absolute = 
-      processAttrl $ change_src `when` hasName "src"
-
-
 --
 -- Tests
 --