aboutsummaryrefslogtreecommitdiff
path: root/Main.hs
diff options
context:
space:
mode:
authorfiddlosopher <fiddlosopher@788f1e2b-df1e-0410-8736-df70ead52e1b>2008-07-31 23:16:02 +0000
committerfiddlosopher <fiddlosopher@788f1e2b-df1e-0410-8736-df70ead52e1b>2008-07-31 23:16:02 +0000
commitd072ad4b66b5cdf5a8f811ae1f78460e34270d58 (patch)
tree6f77dde12c4d5824434e0961f71c9f38f19be4cd /Main.hs
parent504a61a97b9dbd0b55b2b06fd2c1f547d71a1fa1 (diff)
downloadpandoc-d072ad4b66b5cdf5a8f811ae1f78460e34270d58.tar.gz
Added 'odt' output option to pandoc:
Not a writer, but a module that inserts the output of the OpenDocument writer into an ODT archive. This replaces markdown2odt. + Added odt output option to Main.hs. + Added default for .odt output file. + Changed defaults so that .xml and .sgml aren't automatically DocBook. + Added odt writer to Text.Pandoc exports. + Added Text.Pandoc.ODT and included in pandoc.cabal. + Added reference.odt as data-file in pandoc.cabal. + Handle picture links in OpenDocument files using xml library. + Removed markdown2odt and references from Makefile, README, man. git-svn-id: https://pandoc.googlecode.com/svn/trunk@1345 788f1e2b-df1e-0410-8736-df70ead52e1b
Diffstat (limited to 'Main.hs')
-rw-r--r--Main.hs46
1 files changed, 31 insertions, 15 deletions
diff --git a/Main.hs b/Main.hs
index 87ae17ce6..423cf35dc 100644
--- a/Main.hs
+++ b/Main.hs
@@ -31,11 +31,12 @@ writers.
module Main where
import Text.Pandoc
import Text.Pandoc.UTF8
+import Text.Pandoc.ODT
import Text.Pandoc.Shared ( joinWithSep, HTMLMathMethod (..) )
import Text.Pandoc.Highlighting ( languages )
import System.Environment ( getArgs, getProgName, getEnvironment )
import System.Exit ( exitWith, ExitCode (..) )
-import System.FilePath ( takeExtension )
+import System.FilePath ( takeExtension, takeDirectory )
import System.Console.GetOpt
import System.IO
import Data.Maybe ( fromMaybe )
@@ -82,6 +83,7 @@ writers = [("native" , (writeDoc, ""))
,("s5" , (writeS5String, defaultS5Header))
,("docbook" , (writeDocbook, defaultDocbookHeader))
,("opendocument" , (writeOpenDocument, defaultOpenDocumentHeader))
+ ,("odt" , (writeOpenDocument, defaultOpenDocumentHeader))
,("latex" , (writeLaTeX, defaultLaTeXHeader))
,("context" , (writeConTeXt, defaultConTeXtHeader))
,("texinfo" , (writeTexinfo, ""))
@@ -92,6 +94,10 @@ writers = [("native" , (writeDoc, ""))
,("rtf" , (writeRTF, defaultRTFHeader))
]
+isNonTextOutput :: String -> Bool
+isNonTextOutput "odt" = True
+isNonTextOutput _ = False
+
-- | Writer for Pandoc native format.
writeDoc :: WriterOptions -> Pandoc -> String
writeDoc _ = prettyPandoc
@@ -392,8 +398,7 @@ defaultWriterName x =
".texi" -> "texinfo"
".texinfo" -> "texinfo"
".db" -> "docbook"
- ".xml" -> "docbook"
- ".sgml" -> "docbook"
+ ".odt" -> "odt"
['.',y] | y `elem` ['1'..'9'] -> "man"
_ -> "html"
@@ -478,10 +483,6 @@ main = do
Just (w,h) -> return (w, h)
Nothing -> error ("Unknown writer: " ++ writerName')
- output <- if (outputFile == "-")
- then return stdout
- else openFile outputFile WriteMode
-
environment <- getEnvironment
let columns = case lookup "COLUMNS" environment of
Just cols -> read cols
@@ -501,11 +502,13 @@ main = do
tabFilter spsToNextStop (x:xs) =
x:(tabFilter (spsToNextStop - 1) xs)
+ let standalone' = (standalone && not strict) || writerName' == "odt"
+
let startParserState =
defaultParserState { stateParseRaw = parseRaw,
stateTabStop = tabStop,
stateSanitizeHTML = sanitize,
- stateStandalone = standalone && (not strict),
+ stateStandalone = standalone',
stateSmart = smart || writerName' `elem`
["latex", "context"],
stateColumns = columns,
@@ -519,16 +522,15 @@ main = do
let header = (if (customHeader == "DEFAULT")
then defaultHeader
else customHeader) ++ csslink ++ includeHeader
- let writerOptions = WriterOptions { writerStandalone = standalone &&
- (not strict),
+ let writerOptions = WriterOptions { writerStandalone = standalone',
writerHeader = header,
writerTitlePrefix = titlePrefix,
writerTabStop = tabStop,
writerTableOfContents = toc &&
(not strict) &&
- writerName/="s5",
+ writerName' /= "s5",
writerHTMLMathMethod = mathMethod,
- writerS5 = (writerName=="s5"),
+ writerS5 = (writerName' == "s5"),
writerIgnoreNotes = False,
writerIncremental = incremental,
writerNumberSections = numberSections,
@@ -538,11 +540,25 @@ main = do
writerReferenceLinks = referenceLinks,
writerWrapText = wrap }
- (readSources sources) >>= (hPutStrLn output . toUTF8 .
+ let writeOutput = if writerName' == "odt"
+ then if outputFile == "-"
+ then \_ -> do
+ hPutStrLn stderr ("Error: Cannot write " ++ writerName ++
+ " output to stdout.\n" ++
+ "Specify an output file using the -o option.")
+ exitWith $ ExitFailure 5
+ else let sourceDirRelative = if null sources
+ then ""
+ else takeDirectory (head sources)
+ in saveOpenDocumentAsODT outputFile sourceDirRelative
+ else if outputFile == "-"
+ then putStrLn
+ else writeFile outputFile . (++ "\n")
+
+ (readSources sources) >>= writeOutput . toUTF8 .
(writer writerOptions) .
(reader startParserState) . tabFilter tabStop .
- fromUTF8 . (joinWithSep "\n")) >>
- hClose output
+ fromUTF8 . (joinWithSep "\n")
where
readSources [] = mapM readSource ["-"]