Get default stylesheet in EPUB writer, rather than pandoc.hs.

This commit is contained in:
John MacFarlane 2010-07-08 17:51:13 -07:00
parent bf43da01c9
commit 8af979311a
2 changed files with 12 additions and 12 deletions

View file

@ -47,11 +47,14 @@ import Text.Pandoc.Writers.Markdown ( writePlain )
import Data.Char ( toLower ) import Data.Char ( toLower )
-- | Produce an EPUB file from a Pandoc document. -- | Produce an EPUB file from a Pandoc document.
writeEPUB :: String -- ^ EPUB stylesheet writeEPUB :: Maybe String -- ^ EPUB stylesheet specified at command line
-> WriterOptions -- ^ Writer options -> WriterOptions -- ^ Writer options
-> Pandoc -- ^ Document to convert -> Pandoc -- ^ Document to convert
-> IO B.ByteString -> IO B.ByteString
writeEPUB stylesheet opts doc = do writeEPUB mbStylesheet opts doc = do
stylesheet <- case mbStylesheet of
Just s -> return s
Nothing -> readDataFile (writerUserDataDir opts) "epub.css"
(TOD epochtime _) <- getClockTime (TOD epochtime _) <- getClockTime
let opts' = opts{ writerEmailObfuscation = NoObfuscation let opts' = opts{ writerEmailObfuscation = NoObfuscation
, writerStandalone = True , writerStandalone = True

View file

@ -695,16 +695,13 @@ main = do
Just r -> return r Just r -> return r
Nothing -> error ("Unknown reader: " ++ readerName') Nothing -> error ("Unknown reader: " ++ readerName')
writer <- case (lookup writerName' writers) of let writer = case lookup writerName' writers of
Just _ | writerName' == "epub" -> do Just _ | writerName' == "epub" -> writeEPUB epubStylesheet
epubstyle <- case epubStylesheet of Just _ | writerName' == "odt" -> writeODT referenceODT
Just s -> return s Just r -> \o ->
Nothing -> readDataFile datadir "epub.css" return . fromString . r o
return (writeEPUB epubstyle) Nothing -> error $ "Unknown writer: " ++
Just _ | writerName' == "odt" -> return (writeODT referenceODT) writerName'
Just r -> return $ \o d ->
return $ fromString (r o d)
Nothing -> error ("Unknown writer: " ++ writerName')
templ <- getDefaultTemplate datadir writerName' templ <- getDefaultTemplate datadir writerName'
let defaultTemplate = case templ of let defaultTemplate = case templ of