Added writerSourceDirectory to WriterOptions.

This allows us to remove an argument from the ODT and EPUB
writers.
This commit is contained in:
John MacFarlane 2010-07-08 17:14:03 -07:00
parent 8417820498
commit d67ec663ba
4 changed files with 20 additions and 16 deletions

View file

@ -477,6 +477,7 @@ data WriterOptions = WriterOptions
, writerLiterateHaskell :: Bool -- ^ Write as literate haskell
, writerEmailObfuscation :: ObfuscationMethod -- ^ How to obfuscate emails
, writerIdentifierPrefix :: String -- ^ Prefix for section & note ids in HTML
, writerSourceDirectory :: FilePath -- ^ Directory path of 1st source file
} deriving Show
-- | Default writer options.
@ -500,6 +501,7 @@ defaultWriterOptions =
, writerLiterateHaskell = False
, writerEmailObfuscation = JavascriptObfuscation
, writerIdentifierPrefix = ""
, writerSourceDirectory = "."
}
--

View file

@ -47,16 +47,16 @@ import Text.Pandoc.Writers.Markdown ( writePlain )
import Data.Char ( toLower )
-- | Produce an EPUB file from a Pandoc document.
writeEPUB :: FilePath -- ^ Relative directory of source file
-> String -- ^ EPUB stylesheet
writeEPUB :: String -- ^ EPUB stylesheet
-> WriterOptions -- ^ Writer options
-> Pandoc -- ^ Document to convert
-> IO B.ByteString
writeEPUB sourceDir stylesheet opts doc = do
writeEPUB stylesheet opts doc = do
(TOD epochtime _) <- getClockTime
let opts' = opts{ writerEmailObfuscation = NoObfuscation
, writerStandalone = True
, writerWrapText = False }
let sourceDir = writerSourceDirectory opts'
-- mimetype
let mimetypeEntry = toEntry "mimetype" epochtime $ fromString "application/epub+zip"
-- container.xml

View file

@ -35,7 +35,7 @@ import Data.ByteString.Lazy.UTF8 ( fromString )
import Codec.Archive.Zip
import System.Time
import Paths_pandoc ( getDataFileName )
import Text.Pandoc.Shared ( WriterOptions )
import Text.Pandoc.Shared ( WriterOptions(..) )
import Text.Pandoc.Definition
import Text.Pandoc.Writers.OpenDocument ( writeOpenDocument )
import System.Directory
@ -43,12 +43,11 @@ import Control.Monad (liftM)
-- | Produce an ODT file from a Pandoc document.
writeODT :: Maybe FilePath -- ^ Path of user data directory
-> FilePath -- ^ Relative directory of source file
-> Maybe FilePath -- ^ Path specified by --reference-odt
-> WriterOptions -- ^ Writer options
-> Pandoc -- ^ Document to convert
-> IO B.ByteString
writeODT datadir sourceDirRelative mbRefOdt opts doc = do
writeODT datadir mbRefOdt opts doc = do
refArchive <- liftM toArchive $
case mbRefOdt of
Just f -> B.readFile f
@ -63,7 +62,8 @@ writeODT datadir sourceDirRelative mbRefOdt opts doc = do
else defaultODT
-- handle pictures
picEntriesRef <- newIORef ([] :: [Entry])
doc' <- processWithM (transformPic sourceDirRelative picEntriesRef) doc
let sourceDir = writerSourceDirectory opts
doc' <- processWithM (transformPic sourceDir picEntriesRef) doc
let newContents = writeOpenDocument opts doc'
(TOD epochtime _) <- getClockTime
let contentEntry = toEntry "content.xml" epochtime $ fromString newContents
@ -72,10 +72,10 @@ writeODT datadir sourceDirRelative mbRefOdt opts doc = do
return $ fromArchive archive
transformPic :: FilePath -> IORef [Entry] -> Inline -> IO Inline
transformPic sourceDirRelative entriesRef (Image lab (src,tit)) = do
transformPic sourceDir entriesRef (Image lab (src,tit)) = do
entries <- readIORef entriesRef
let newsrc = "Pictures/" ++ show (length entries) ++ takeExtension src
catch (readEntry [] (sourceDirRelative </> src) >>= \entry ->
catch (readEntry [] (sourceDir </> src) >>= \entry ->
modifyIORef entriesRef (entry{ eRelativePath = newsrc } :) >>
return (Image lab (newsrc, tit)))
(\_ -> return (Emph lab))

View file

@ -672,10 +672,6 @@ main = do
Nothing -> return ()
let sources = if ignoreArgs then [] else args
let sourceDirRelative = if null sources
then ""
else takeDirectory (head sources)
datadir <- case mbDataDir of
Nothing -> catch
@ -704,9 +700,9 @@ main = do
epubstyle <- case epubStylesheet of
Just s -> return s
Nothing -> readDataFile datadir "epub.css"
return (writeEPUB sourceDirRelative epubstyle)
return (writeEPUB epubstyle)
Just _ | writerName' == "odt" -> return
(writeODT datadir sourceDirRelative referenceODT)
(writeODT datadir referenceODT)
Just r -> return $ \o d ->
return $ fromString (r o d)
Nothing -> error ("Unknown writer: " ++ writerName')
@ -742,6 +738,10 @@ main = do
return $ ("mathml-script", s) : variables'
_ -> return variables'
let sourceDir = if null sources
then "."
else takeDirectory (head sources)
let startParserState =
defaultParserState { stateParseRaw = parseRaw,
stateTabStop = tabStop,
@ -757,6 +757,7 @@ main = do
stateColumns = columns,
stateStrict = strict,
stateIndentedCodeClasses = codeBlockClasses }
let writerOptions = WriterOptions { writerStandalone = standalone',
writerTemplate = if null template
then defaultTemplate
@ -780,7 +781,8 @@ main = do
writerEmailObfuscation = if strict
then ReferenceObfuscation
else obfuscationMethod,
writerIdentifierPrefix = idPrefix }
writerIdentifierPrefix = idPrefix,
writerSourceDirectory = sourceDir }
when (isNonTextOutput writerName' && outputFile == "-") $
do UTF8.hPutStrLn stderr ("Error: Cannot write " ++ writerName ++ " output to stdout.\n" ++