]> gitweb.michael.orlitzky.com - dead/lwn-epub.git/blobdiff - src/Epublishable.hs
Use cmdargs to parse the one command-line argument.
[dead/lwn-epub.git] / src / Epublishable.hs
index 01d27f9afe7c648250377d38003607dc707037f1..3ca9b68b57babd9c6fa22e24defe059afdcca814 100644 (file)
@@ -1,14 +1,13 @@
 module Epublishable
 where
 
-import Codec.EBook
-import qualified Data.ByteString.Lazy as B (writeFile)
-import Data.List (foldl')
+import Text.Pandoc
+import qualified Data.ByteString.Lazy as B (ByteString, writeFile)
+import Data.Time (getCurrentTime)
 import Data.Tree.NTree.TypeDefs (NTree)
 import System.FilePath (normalise)
 import Text.XML.HXT.Core (IOSArrow, XNode, XmlTree)
 
-import Misc (string_to_bytestring)
 import XHTML
 
 
@@ -17,21 +16,28 @@ class (XHTML a) => Epublishable a where
 
   title :: a -> String
 
-  epublish :: a -> FilePath -> Integer -> IO ()
-  epublish obj path time = do
-    let book_name = title obj
-    let book =
-          emptyBook { 
-            bookID = "http://lwn.net/" ++ book_name,
-            bookAuthor = "LWN <http://lwn.net> Copyright Eklektix, Inc.",
-            bookTitle = book_name
-          }
+  metadata :: a -> IO String
+  metadata obj = do
+    date <- getCurrentTime
+    return $
+      "<dc:creator>http://lwn.net/</dc:creator>\n" ++
+      "<dc:date>" ++ (show date) ++ "</dc:date>\n" ++
+      "<dc:language>en-US</dc:language>\n" ++
+      "<dc:rights>Copyright Eklektix, Inc.</dc:rights>\n" ++
+      "<dc:title>" ++ (title obj) ++ "</dc:title>\n"
+
+  epublish :: a -> FilePath -> IO ()
+  epublish obj path = do
     let xhtml = to_xhtml obj
-    bs_xhtml <- string_to_bytestring xhtml
-    let iid = "iid-1"
+    epmd <- metadata obj
+    epub <- xhtml_to_epub epmd xhtml
     let normalized_path = normalise path
-    let metadata = Just (ChapterMetadata book_name)
-    let bi = BookItem iid normalized_path bs_xhtml opsMediatype metadata
-    let bookFull = foldl' addItem2Book book [bi]
-    let outdata = book2Bin bookFull time
-    B.writeFile normalized_path outdata
+    B.writeFile normalized_path 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