2006-12-20 21:54:23 +01:00
|
|
|
{-
|
2012-01-31 17:58:30 +01:00
|
|
|
Copyright (C) 2006-2012 John MacFarlane <jgm@berkeley.edu>
|
2006-12-20 21:54:23 +01:00
|
|
|
|
|
|
|
This program is free software; you can redistribute it and/or modify
|
|
|
|
it under the terms of the GNU General Public License as published by
|
|
|
|
the Free Software Foundation; either version 2 of the License, or
|
|
|
|
(at your option) any later version.
|
|
|
|
|
|
|
|
This program is distributed in the hope that it will be useful,
|
|
|
|
but WITHOUT ANY WARRANTY; without even the implied warranty of
|
|
|
|
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
|
|
|
|
GNU General Public License for more details.
|
|
|
|
|
|
|
|
You should have received a copy of the GNU General Public License
|
|
|
|
along with this program; if not, write to the Free Software
|
|
|
|
Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
|
|
|
|
-}
|
|
|
|
|
2006-12-20 07:50:14 +01:00
|
|
|
{- |
|
|
|
|
Module : Main
|
2012-01-31 17:58:30 +01:00
|
|
|
Copyright : Copyright (C) 2006-2012 John MacFarlane
|
2008-08-10 19:33:20 +02:00
|
|
|
License : GNU GPL, version 2 or above
|
2006-12-20 07:50:14 +01:00
|
|
|
|
2007-07-08 00:51:55 +02:00
|
|
|
Maintainer : John MacFarlane <jgm@berkeley@edu>
|
2008-08-10 19:33:20 +02:00
|
|
|
Stability : alpha
|
2006-12-20 07:50:14 +01:00
|
|
|
Portability : portable
|
|
|
|
|
|
|
|
Parses command-line options and calls the appropriate readers and
|
|
|
|
writers.
|
|
|
|
-}
|
2006-10-17 16:22:29 +02:00
|
|
|
module Main where
|
2007-07-12 10:31:05 +02:00
|
|
|
import Text.Pandoc
|
2012-01-21 06:36:04 +01:00
|
|
|
import Text.Pandoc.PDF (tex2pdf)
|
2012-01-30 08:54:00 +01:00
|
|
|
import Text.Pandoc.Readers.LaTeX (handleIncludes)
|
2010-07-12 05:03:55 +02:00
|
|
|
import Text.Pandoc.Shared ( tabFilter, ObfuscationMethod (..), readDataFile,
|
2012-01-30 08:54:00 +01:00
|
|
|
headerShift, findDataFile, normalize, err, warn )
|
2012-02-05 23:37:33 +01:00
|
|
|
import Text.Pandoc.XML ( toEntities, fromEntities )
|
2011-11-22 00:24:28 +01:00
|
|
|
import Text.Pandoc.SelfContained ( makeSelfContained )
|
2011-12-28 08:46:23 +01:00
|
|
|
import Text.Pandoc.Highlighting ( languages, Style, tango, pygments,
|
|
|
|
espresso, kate, haddock, monochrome )
|
2010-12-13 05:09:14 +01:00
|
|
|
import System.Environment ( getArgs, getProgName )
|
2007-01-08 17:29:29 +01:00
|
|
|
import System.Exit ( exitWith, ExitCode (..) )
|
2009-01-24 20:58:06 +01:00
|
|
|
import System.FilePath
|
2006-10-17 16:22:29 +02:00
|
|
|
import System.Console.GetOpt
|
2010-12-13 05:09:14 +01:00
|
|
|
import Data.Char ( toLower )
|
2011-12-30 02:41:06 +01:00
|
|
|
import Data.List ( intercalate, isSuffixOf, isPrefixOf )
|
2012-01-21 07:12:03 +01:00
|
|
|
import System.Directory ( getAppUserDataDirectory, doesFileExist, findExecutable )
|
2012-01-30 08:54:00 +01:00
|
|
|
import System.IO ( stdout )
|
2011-07-23 07:15:25 +02:00
|
|
|
import System.IO.Error ( isDoesNotExistError )
|
|
|
|
import Control.Exception.Extensible ( throwIO )
|
2010-05-07 05:29:44 +02:00
|
|
|
import qualified Text.Pandoc.UTF8 as UTF8
|
2011-12-28 08:46:23 +01:00
|
|
|
import qualified Text.CSL as CSL
|
2008-08-04 05:15:34 +02:00
|
|
|
import Text.Pandoc.Biblio
|
2010-02-21 17:47:24 +01:00
|
|
|
import Control.Monad (when, unless, liftM)
|
2010-03-15 00:23:26 +01:00
|
|
|
import Network.HTTP (simpleHTTP, mkRequest, getResponseBody, RequestMethod(..))
|
2010-11-13 03:30:50 +01:00
|
|
|
import Network.URI (parseURI, isURI, URI(..))
|
2010-07-03 05:12:14 +02:00
|
|
|
import qualified Data.ByteString.Lazy as B
|
2011-01-30 19:29:10 +01:00
|
|
|
import Data.ByteString.Lazy.UTF8 (toString )
|
2010-09-11 04:53:45 +02:00
|
|
|
import Codec.Binary.UTF8.String (decodeString, encodeString)
|
2011-12-30 08:11:42 +01:00
|
|
|
import Text.CSL.Reference (Reference(..))
|
2006-10-17 16:22:29 +02:00
|
|
|
|
2006-12-22 21:16:03 +01:00
|
|
|
copyrightMessage :: String
|
2012-01-31 17:58:30 +01:00
|
|
|
copyrightMessage = "\nCopyright (C) 2006-2012 John MacFarlane\n" ++
|
2008-08-01 01:55:27 +02:00
|
|
|
"Web: http://johnmacfarlane.net/pandoc\n" ++
|
|
|
|
"This is free software; see the source for copying conditions. There is no\n" ++
|
|
|
|
"warranty, not even for merchantability or fitness for a particular purpose."
|
2006-12-22 21:16:03 +01:00
|
|
|
|
2008-08-04 01:33:40 +02:00
|
|
|
compileInfo :: String
|
2008-08-04 05:15:34 +02:00
|
|
|
compileInfo =
|
2012-02-12 01:21:37 +01:00
|
|
|
"\nCompiled with citeproc-hs " ++ VERSION_citeproc_hs ++ ", texmath " ++
|
|
|
|
VERSION_texmath ++ ", highlighting-kate " ++ VERSION_highlighting_kate ++
|
2011-12-29 23:17:10 +01:00
|
|
|
".\nSyntax highlighting is supported for the following languages:\n " ++
|
2011-12-29 22:53:25 +01:00
|
|
|
wrapWords 4 78 languages
|
2008-02-09 04:22:01 +01:00
|
|
|
|
2008-09-30 22:16:03 +02:00
|
|
|
-- | Converts a list of strings into a single string with the items printed as
|
|
|
|
-- comma separated words in lines with a maximum line length.
|
2011-12-29 22:53:25 +01:00
|
|
|
wrapWords :: Int -> Int -> [String] -> String
|
|
|
|
wrapWords indent c = wrap' (c - indent) (c - indent)
|
|
|
|
where wrap' _ _ [] = ""
|
2008-09-30 22:16:03 +02:00
|
|
|
wrap' cols remaining (x:xs) = if remaining == cols
|
|
|
|
then x ++ wrap' cols (remaining - length x) xs
|
|
|
|
else if (length x + 1) > remaining
|
2011-12-29 22:53:25 +01:00
|
|
|
then ",\n" ++ replicate indent ' ' ++ x ++ wrap' cols (cols - length x) xs
|
2008-09-30 22:16:03 +02:00
|
|
|
else ", " ++ x ++ wrap' cols (remaining - (length x + 2)) xs
|
2008-02-09 04:21:19 +01:00
|
|
|
|
2012-01-03 21:10:10 +01:00
|
|
|
nonTextFormats :: [String]
|
2012-01-28 20:41:26 +01:00
|
|
|
nonTextFormats = ["odt","docx","epub"]
|
2008-08-01 01:16:02 +02:00
|
|
|
|
2006-10-17 16:22:29 +02:00
|
|
|
-- | Data structure for command line options.
|
|
|
|
data Opt = Opt
|
2009-01-31 18:13:41 +01:00
|
|
|
{ optTabStop :: Int -- ^ Number of spaces per tab
|
2009-04-08 22:19:50 +02:00
|
|
|
, optPreserveTabs :: Bool -- ^ Preserve tabs instead of converting to spaces
|
2006-12-30 23:51:49 +01:00
|
|
|
, optStandalone :: Bool -- ^ Include header, footer
|
2006-12-28 03:20:09 +01:00
|
|
|
, optReader :: String -- ^ Reader format
|
|
|
|
, optWriter :: String -- ^ Writer format
|
2006-12-30 23:51:49 +01:00
|
|
|
, optParseRaw :: Bool -- ^ Parse unconvertable HTML and TeX
|
2007-07-07 07:43:23 +02:00
|
|
|
, optTableOfContents :: Bool -- ^ Include table of contents
|
2010-03-18 07:45:28 +01:00
|
|
|
, optTransforms :: [Pandoc -> Pandoc] -- ^ Doc transforms to apply
|
2011-07-23 07:15:25 +02:00
|
|
|
, optTemplate :: Maybe FilePath -- ^ Custom template
|
2009-12-31 02:09:56 +01:00
|
|
|
, optVariables :: [(String,String)] -- ^ Template variables to set
|
2006-12-22 21:16:03 +01:00
|
|
|
, optOutputFile :: String -- ^ Name of output file
|
2006-12-30 23:51:49 +01:00
|
|
|
, optNumberSections :: Bool -- ^ Number sections in LaTeX
|
2010-07-16 04:01:00 +02:00
|
|
|
, optSectionDivs :: Bool -- ^ Put sections in div tags in HTML
|
2010-07-14 05:44:56 +02:00
|
|
|
, optIncremental :: Bool -- ^ Use incremental lists in Slidy/S5
|
2011-11-22 00:24:28 +01:00
|
|
|
, optSelfContained :: Bool -- ^ Make HTML accessible offline
|
2006-12-30 23:51:49 +01:00
|
|
|
, optSmart :: Bool -- ^ Use smart typography
|
2012-01-01 22:48:28 +01:00
|
|
|
, optOldDashes :: Bool -- ^ Parse dashes like pandoc <=1.8.2.1
|
2011-01-12 05:37:06 +01:00
|
|
|
, optHtml5 :: Bool -- ^ Produce HTML5 in HTML
|
2011-12-28 08:46:23 +01:00
|
|
|
, optHighlight :: Bool -- ^ Highlight source code
|
|
|
|
, optHighlightStyle :: Style -- ^ Style to use for highlighted code
|
2011-01-16 17:57:32 +01:00
|
|
|
, optChapters :: Bool -- ^ Use chapter for top-level sects
|
2007-12-01 04:11:52 +01:00
|
|
|
, optHTMLMathMethod :: HTMLMathMethod -- ^ Method to print HTML math
|
2009-12-31 23:40:59 +01:00
|
|
|
, optReferenceODT :: Maybe FilePath -- ^ Path of reference.odt
|
2012-01-03 21:10:10 +01:00
|
|
|
, optReferenceDocx :: Maybe FilePath -- ^ Path of reference.docx
|
2010-07-03 07:07:00 +02:00
|
|
|
, optEPUBStylesheet :: Maybe String -- ^ EPUB stylesheet
|
2010-07-05 01:56:17 +02:00
|
|
|
, optEPUBMetadata :: String -- ^ EPUB metadata
|
2012-01-30 20:45:55 +01:00
|
|
|
, optEPUBFonts :: [FilePath] -- ^ EPUB fonts to embed
|
Changes to Pandoc's options to facilitate wrapper scripts:
+ removed -d/--debug option
+ added --dump-args option, which prints the name of the output file
(or '-' for STDOUT) and all the command-line arguments (excluding
Pandoc options and their arguments), one per line, then exits. Note
that special wrapper options will be treated as arguments if they
follow '--' at the end of the command line. Thus,
pandoc --dump-args -o foo.html foo.txt -- -e latin1
will print the following to STDOUT:
foo.html
foo.txt
-e
latin1
+ added --ignore-args option, which causes Pandoc to ignore all
(non-option) arguments, including any special options that occur
after '--' at the end of the command line.
+ '-' now means STDIN as the name of an input file, STDOUT as the
name of an output file. So,
pandoc -o - -
will take input from STDIN and print output to STDOUT. Note that
if multiple '-o' options are specified on the same line, the last
one takes precedence. So, in a script,
pandoc "$@" -o -
will guarantee output to STDOUT, even if the '-o' option was used.
+ documented these changes in man pages, README, and changelog.
git-svn-id: https://pandoc.googlecode.com/svn/trunk@454 788f1e2b-df1e-0410-8736-df70ead52e1b
2007-01-08 09:11:08 +01:00
|
|
|
, optDumpArgs :: Bool -- ^ Output command-line arguments
|
|
|
|
, optIgnoreArgs :: Bool -- ^ Ignore command-line arguments
|
2006-12-30 23:51:49 +01:00
|
|
|
, optStrict :: Bool -- ^ Use strict markdown syntax
|
Extensive changes stemming from a rethinking of the Pandoc data
structure. Key and Note blocks have been removed. Link and image URLs
are now stored directly in Link and Image inlines, and note blocks
are stored in Note inlines. This requires changes in both parsers
and writers. Markdown and RST parsers need to extract data from key
and note blocks and insert them into the relevant inline elements.
Other parsers can be simplified, since there is no longer any need to
construct separate key and note blocks. Markdown, RST, and HTML writers
need to construct lists of notes; Markdown and RST writers need to
construct lists of link references (when the --reference-links option
is specified); and the RST writer needs to construct a list of image
substitution references. All writers have been rewritten to use the
State monad when state is required. This rewrite yields a small speed
boost and considerably cleaner code.
* Text/Pandoc/Definition.hs:
+ blocks: removed Key and Note
+ inlines: removed NoteRef, added Note
+ modified Target: there is no longer a 'Ref' target; all targets
are explicit URL, title pairs
* Text/Pandoc/Shared.hs:
+ Added 'Reference', 'isNoteBlock', 'isKeyBlock', 'isLineClump',
used in some of the readers.
+ Removed 'generateReference', 'keyTable', 'replaceReferenceLinks',
'replaceRefLinksBlockList', along with some auxiliary functions
used only by them. These are no longer needed, since
reference links are resolved in the Markdown and RST readers.
+ Moved 'inTags', 'selfClosingTag', 'inTagsSimple', and 'inTagsIndented'
to the Docbook writer, since that is now the only module that uses
them.
+ Changed name of 'escapeSGMLString' to 'escapeStringForXML'
+ Added KeyTable and NoteTable types
+ Removed fields from ParserState; 'stateKeyBlocks', 'stateKeysUsed',
'stateNoteBlocks', 'stateNoteIdentifiers', 'stateInlineLinks'.
Added 'stateKeys' and 'stateNotes'.
+ Added clause for Note to 'prettyBlock'.
+ Added 'writerNotes', 'writerReferenceLinks' fields to WriterOptions.
* Text/Pandoc/Entities.hs: Renamed 'escapeSGMLChar' and
'escapeSGMLString' to 'escapeCharForXML' and 'escapeStringForXML'
* Text/ParserCombinators/Pandoc.hs: Added lineClump parser: parses a raw
line block up to and including following blank lines.
* Main.hs: Replaced --inline-links with --reference-links.
* README:
+ Documented --reference-links and removed description of --inline-links.
+ Added note that footnotes may occur anywhere in the document, but must
be at the outer level, not embedded in block elements.
* man/man1/pandoc.1, man/man1/html2markdown.1: Removed --inline-links
option, added --reference-links option
* Markdown and RST readers:
+ Rewrote to fit new Pandoc definition. Since there are no longer
Note or Key blocks, all note and key blocks are parsed on a first pass
through the document. Once tables of notes and keys have been constructed,
the remaining parts of the document are reassembled and parsed.
+ Refactored link parsers.
* LaTeX and HTML readers: Rewrote to fit new Pandoc definition. Since
there are no longer Note or Key blocks, notes and references can be
parsed in a single pass through the document.
* RST, Markdown, and HTML writers: Rewrote using state monad new Pandoc
and definition. State is used to hold lists of references footnotes to
and be printed at the end of the document.
* RTF and LaTeX writers: Rewrote using new Pandoc definition. (Because
of the different treatment of footnotes, the "notes" parameter is no
longer needed in the block and inline conversion functions.)
* Docbook writer:
+ Moved the functions 'attributeList', 'inTags', 'selfClosingTag',
'inTagsSimple', 'inTagsIndented' from Text/Pandoc/Shared, since
they are now used only by the Docbook writer.
+ Rewrote using new Pandoc definition. (Because of the different
treatment of footnotes, the "notes" parameter is no longer needed
in the block and inline conversion functions.)
* Updated test suite
* Throughout: old haskell98 module names replaced by hierarchical module
names, e.g. List by Data.List.
* debian/control: Include libghc6-xhtml-dev instead of libghc6-html-dev
in "Build-Depends."
* cabalize:
+ Remove haskell98 from BASE_DEPENDS (since now the new hierarchical
module names are being used throughout)
+ Added mtl to BASE_DEPENDS (needed for state monad)
+ Removed html from GHC66_DEPENDS (not needed since xhtml is now used)
git-svn-id: https://pandoc.googlecode.com/svn/trunk@580 788f1e2b-df1e-0410-8736-df70ead52e1b
2007-04-10 03:56:50 +02:00
|
|
|
, optReferenceLinks :: Bool -- ^ Use reference links in writing markdown, rst
|
2007-09-27 03:23:44 +02:00
|
|
|
, optWrapText :: Bool -- ^ Wrap text
|
2010-12-13 05:09:14 +01:00
|
|
|
, optColumns :: Int -- ^ Line length in characters
|
2009-01-24 20:58:06 +01:00
|
|
|
, optPlugins :: [Pandoc -> IO Pandoc] -- ^ Plugins to apply
|
2009-01-24 20:58:48 +01:00
|
|
|
, optEmailObfuscation :: ObfuscationMethod
|
2009-12-05 18:56:02 +01:00
|
|
|
, optIdentifierPrefix :: String
|
2009-12-05 05:46:57 +01:00
|
|
|
, optIndentedCodeClasses :: [String] -- ^ Default classes for indented code blocks
|
2010-01-14 06:54:38 +01:00
|
|
|
, optDataDir :: Maybe FilePath
|
2010-12-13 21:18:01 +01:00
|
|
|
, optCiteMethod :: CiteMethod -- ^ Method to output cites
|
|
|
|
, optBibliography :: [String]
|
2010-11-18 23:15:26 +01:00
|
|
|
, optCslFile :: FilePath
|
2011-11-12 02:36:57 +01:00
|
|
|
, optAbbrevsFile :: Maybe FilePath
|
2011-01-17 23:54:51 +01:00
|
|
|
, optListings :: Bool -- ^ Use listings package for code blocks
|
2012-01-21 23:46:27 +01:00
|
|
|
, optLaTeXEngine :: String -- ^ Program to use for latex -> pdf
|
2012-01-26 02:50:03 +01:00
|
|
|
, optSlideLevel :: Maybe Int -- ^ Header level that creates slides
|
2012-01-27 08:55:37 +01:00
|
|
|
, optSetextHeaders :: Bool -- ^ Use atx headers for markdown level 1-2
|
2012-02-05 23:58:55 +01:00
|
|
|
, optAscii :: Bool -- ^ Use ascii characters only in html
|
2006-10-17 16:22:29 +02:00
|
|
|
}
|
|
|
|
|
|
|
|
-- | Defaults for command-line options.
|
2006-12-28 03:20:09 +01:00
|
|
|
defaultOpts :: Opt
|
|
|
|
defaultOpts = Opt
|
2009-01-31 18:13:41 +01:00
|
|
|
{ optTabStop = 4
|
2009-04-08 22:19:50 +02:00
|
|
|
, optPreserveTabs = False
|
2006-10-17 16:22:29 +02:00
|
|
|
, optStandalone = False
|
2006-12-28 03:20:09 +01:00
|
|
|
, optReader = "" -- null for default reader
|
|
|
|
, optWriter = "" -- null for default writer
|
2006-10-17 16:22:29 +02:00
|
|
|
, optParseRaw = False
|
2007-07-07 07:43:23 +02:00
|
|
|
, optTableOfContents = False
|
2010-03-18 07:45:28 +01:00
|
|
|
, optTransforms = []
|
2011-07-23 07:15:25 +02:00
|
|
|
, optTemplate = Nothing
|
2009-12-31 02:09:56 +01:00
|
|
|
, optVariables = []
|
Changes to Pandoc's options to facilitate wrapper scripts:
+ removed -d/--debug option
+ added --dump-args option, which prints the name of the output file
(or '-' for STDOUT) and all the command-line arguments (excluding
Pandoc options and their arguments), one per line, then exits. Note
that special wrapper options will be treated as arguments if they
follow '--' at the end of the command line. Thus,
pandoc --dump-args -o foo.html foo.txt -- -e latin1
will print the following to STDOUT:
foo.html
foo.txt
-e
latin1
+ added --ignore-args option, which causes Pandoc to ignore all
(non-option) arguments, including any special options that occur
after '--' at the end of the command line.
+ '-' now means STDIN as the name of an input file, STDOUT as the
name of an output file. So,
pandoc -o - -
will take input from STDIN and print output to STDOUT. Note that
if multiple '-o' options are specified on the same line, the last
one takes precedence. So, in a script,
pandoc "$@" -o -
will guarantee output to STDOUT, even if the '-o' option was used.
+ documented these changes in man pages, README, and changelog.
git-svn-id: https://pandoc.googlecode.com/svn/trunk@454 788f1e2b-df1e-0410-8736-df70ead52e1b
2007-01-08 09:11:08 +01:00
|
|
|
, optOutputFile = "-" -- "-" means stdout
|
2006-10-17 16:22:29 +02:00
|
|
|
, optNumberSections = False
|
2010-07-16 04:01:00 +02:00
|
|
|
, optSectionDivs = False
|
2006-10-17 16:22:29 +02:00
|
|
|
, optIncremental = False
|
2011-11-22 00:24:28 +01:00
|
|
|
, optSelfContained = False
|
2006-12-18 23:02:39 +01:00
|
|
|
, optSmart = False
|
2012-01-01 22:48:28 +01:00
|
|
|
, optOldDashes = False
|
2011-01-12 05:37:06 +01:00
|
|
|
, optHtml5 = False
|
2011-12-28 08:46:23 +01:00
|
|
|
, optHighlight = True
|
|
|
|
, optHighlightStyle = pygments
|
2011-01-16 17:57:32 +01:00
|
|
|
, optChapters = False
|
2007-12-01 04:11:52 +01:00
|
|
|
, optHTMLMathMethod = PlainMath
|
2009-12-31 23:40:59 +01:00
|
|
|
, optReferenceODT = Nothing
|
2012-01-03 21:10:10 +01:00
|
|
|
, optReferenceDocx = Nothing
|
2010-07-03 07:07:00 +02:00
|
|
|
, optEPUBStylesheet = Nothing
|
2010-07-05 01:56:17 +02:00
|
|
|
, optEPUBMetadata = ""
|
2012-01-30 20:45:55 +01:00
|
|
|
, optEPUBFonts = []
|
Changes to Pandoc's options to facilitate wrapper scripts:
+ removed -d/--debug option
+ added --dump-args option, which prints the name of the output file
(or '-' for STDOUT) and all the command-line arguments (excluding
Pandoc options and their arguments), one per line, then exits. Note
that special wrapper options will be treated as arguments if they
follow '--' at the end of the command line. Thus,
pandoc --dump-args -o foo.html foo.txt -- -e latin1
will print the following to STDOUT:
foo.html
foo.txt
-e
latin1
+ added --ignore-args option, which causes Pandoc to ignore all
(non-option) arguments, including any special options that occur
after '--' at the end of the command line.
+ '-' now means STDIN as the name of an input file, STDOUT as the
name of an output file. So,
pandoc -o - -
will take input from STDIN and print output to STDOUT. Note that
if multiple '-o' options are specified on the same line, the last
one takes precedence. So, in a script,
pandoc "$@" -o -
will guarantee output to STDOUT, even if the '-o' option was used.
+ documented these changes in man pages, README, and changelog.
git-svn-id: https://pandoc.googlecode.com/svn/trunk@454 788f1e2b-df1e-0410-8736-df70ead52e1b
2007-01-08 09:11:08 +01:00
|
|
|
, optDumpArgs = False
|
|
|
|
, optIgnoreArgs = False
|
2006-12-30 23:51:49 +01:00
|
|
|
, optStrict = False
|
Extensive changes stemming from a rethinking of the Pandoc data
structure. Key and Note blocks have been removed. Link and image URLs
are now stored directly in Link and Image inlines, and note blocks
are stored in Note inlines. This requires changes in both parsers
and writers. Markdown and RST parsers need to extract data from key
and note blocks and insert them into the relevant inline elements.
Other parsers can be simplified, since there is no longer any need to
construct separate key and note blocks. Markdown, RST, and HTML writers
need to construct lists of notes; Markdown and RST writers need to
construct lists of link references (when the --reference-links option
is specified); and the RST writer needs to construct a list of image
substitution references. All writers have been rewritten to use the
State monad when state is required. This rewrite yields a small speed
boost and considerably cleaner code.
* Text/Pandoc/Definition.hs:
+ blocks: removed Key and Note
+ inlines: removed NoteRef, added Note
+ modified Target: there is no longer a 'Ref' target; all targets
are explicit URL, title pairs
* Text/Pandoc/Shared.hs:
+ Added 'Reference', 'isNoteBlock', 'isKeyBlock', 'isLineClump',
used in some of the readers.
+ Removed 'generateReference', 'keyTable', 'replaceReferenceLinks',
'replaceRefLinksBlockList', along with some auxiliary functions
used only by them. These are no longer needed, since
reference links are resolved in the Markdown and RST readers.
+ Moved 'inTags', 'selfClosingTag', 'inTagsSimple', and 'inTagsIndented'
to the Docbook writer, since that is now the only module that uses
them.
+ Changed name of 'escapeSGMLString' to 'escapeStringForXML'
+ Added KeyTable and NoteTable types
+ Removed fields from ParserState; 'stateKeyBlocks', 'stateKeysUsed',
'stateNoteBlocks', 'stateNoteIdentifiers', 'stateInlineLinks'.
Added 'stateKeys' and 'stateNotes'.
+ Added clause for Note to 'prettyBlock'.
+ Added 'writerNotes', 'writerReferenceLinks' fields to WriterOptions.
* Text/Pandoc/Entities.hs: Renamed 'escapeSGMLChar' and
'escapeSGMLString' to 'escapeCharForXML' and 'escapeStringForXML'
* Text/ParserCombinators/Pandoc.hs: Added lineClump parser: parses a raw
line block up to and including following blank lines.
* Main.hs: Replaced --inline-links with --reference-links.
* README:
+ Documented --reference-links and removed description of --inline-links.
+ Added note that footnotes may occur anywhere in the document, but must
be at the outer level, not embedded in block elements.
* man/man1/pandoc.1, man/man1/html2markdown.1: Removed --inline-links
option, added --reference-links option
* Markdown and RST readers:
+ Rewrote to fit new Pandoc definition. Since there are no longer
Note or Key blocks, all note and key blocks are parsed on a first pass
through the document. Once tables of notes and keys have been constructed,
the remaining parts of the document are reassembled and parsed.
+ Refactored link parsers.
* LaTeX and HTML readers: Rewrote to fit new Pandoc definition. Since
there are no longer Note or Key blocks, notes and references can be
parsed in a single pass through the document.
* RST, Markdown, and HTML writers: Rewrote using state monad new Pandoc
and definition. State is used to hold lists of references footnotes to
and be printed at the end of the document.
* RTF and LaTeX writers: Rewrote using new Pandoc definition. (Because
of the different treatment of footnotes, the "notes" parameter is no
longer needed in the block and inline conversion functions.)
* Docbook writer:
+ Moved the functions 'attributeList', 'inTags', 'selfClosingTag',
'inTagsSimple', 'inTagsIndented' from Text/Pandoc/Shared, since
they are now used only by the Docbook writer.
+ Rewrote using new Pandoc definition. (Because of the different
treatment of footnotes, the "notes" parameter is no longer needed
in the block and inline conversion functions.)
* Updated test suite
* Throughout: old haskell98 module names replaced by hierarchical module
names, e.g. List by Data.List.
* debian/control: Include libghc6-xhtml-dev instead of libghc6-html-dev
in "Build-Depends."
* cabalize:
+ Remove haskell98 from BASE_DEPENDS (since now the new hierarchical
module names are being used throughout)
+ Added mtl to BASE_DEPENDS (needed for state monad)
+ Removed html from GHC66_DEPENDS (not needed since xhtml is now used)
git-svn-id: https://pandoc.googlecode.com/svn/trunk@580 788f1e2b-df1e-0410-8736-df70ead52e1b
2007-04-10 03:56:50 +02:00
|
|
|
, optReferenceLinks = False
|
2007-09-27 03:23:44 +02:00
|
|
|
, optWrapText = True
|
2010-12-13 05:09:14 +01:00
|
|
|
, optColumns = 72
|
2009-01-24 20:58:06 +01:00
|
|
|
, optPlugins = []
|
2009-01-24 20:58:48 +01:00
|
|
|
, optEmailObfuscation = JavascriptObfuscation
|
2009-12-05 18:56:02 +01:00
|
|
|
, optIdentifierPrefix = ""
|
2009-12-05 05:46:57 +01:00
|
|
|
, optIndentedCodeClasses = []
|
2010-01-14 06:54:38 +01:00
|
|
|
, optDataDir = Nothing
|
2010-12-13 21:18:01 +01:00
|
|
|
, optCiteMethod = Citeproc
|
2010-11-13 17:42:09 +01:00
|
|
|
, optBibliography = []
|
2010-11-18 23:15:26 +01:00
|
|
|
, optCslFile = ""
|
2011-11-12 02:36:57 +01:00
|
|
|
, optAbbrevsFile = Nothing
|
2011-01-17 23:54:51 +01:00
|
|
|
, optListings = False
|
2012-01-21 23:46:27 +01:00
|
|
|
, optLaTeXEngine = "pdflatex"
|
2012-01-26 02:50:03 +01:00
|
|
|
, optSlideLevel = Nothing
|
2012-01-27 08:55:37 +01:00
|
|
|
, optSetextHeaders = True
|
2012-02-05 23:58:55 +01:00
|
|
|
, optAscii = False
|
2006-10-17 16:22:29 +02:00
|
|
|
}
|
|
|
|
|
2006-12-28 03:20:09 +01:00
|
|
|
-- | A list of functions, each transforming the options data structure
|
|
|
|
-- in response to a command-line option.
|
|
|
|
options :: [OptDescr (Opt -> IO Opt)]
|
|
|
|
options =
|
2006-12-22 21:16:03 +01:00
|
|
|
[ Option "fr" ["from","read"]
|
2006-10-17 16:22:29 +02:00
|
|
|
(ReqArg
|
2006-12-28 03:20:09 +01:00
|
|
|
(\arg opt -> return opt { optReader = map toLower arg })
|
2006-10-17 16:22:29 +02:00
|
|
|
"FORMAT")
|
2010-12-11 02:30:32 +01:00
|
|
|
""
|
2006-10-17 16:22:29 +02:00
|
|
|
|
|
|
|
, Option "tw" ["to","write"]
|
|
|
|
(ReqArg
|
2006-12-28 03:20:09 +01:00
|
|
|
(\arg opt -> return opt { optWriter = map toLower arg })
|
2006-10-17 16:22:29 +02:00
|
|
|
"FORMAT")
|
2010-12-11 02:30:32 +01:00
|
|
|
""
|
2008-08-10 19:33:20 +02:00
|
|
|
|
2006-12-22 21:16:03 +01:00
|
|
|
, Option "o" ["output"]
|
|
|
|
(ReqArg
|
2006-12-28 03:20:09 +01:00
|
|
|
(\arg opt -> return opt { optOutputFile = arg })
|
2006-12-22 21:16:03 +01:00
|
|
|
"FILENAME")
|
2006-12-31 02:12:01 +01:00
|
|
|
"" -- "Name of output file"
|
2006-12-22 21:16:03 +01:00
|
|
|
|
2012-01-26 07:45:49 +01:00
|
|
|
, Option "" ["data-dir"]
|
2006-10-17 16:22:29 +02:00
|
|
|
(ReqArg
|
2012-01-26 07:45:49 +01:00
|
|
|
(\arg opt -> return opt { optDataDir = Just arg })
|
|
|
|
"DIRECTORY") -- "Directory containing pandoc data files."
|
|
|
|
""
|
2006-10-17 16:22:29 +02:00
|
|
|
|
2006-12-30 23:51:49 +01:00
|
|
|
, Option "" ["strict"]
|
|
|
|
(NoArg
|
|
|
|
(\opt -> return opt { optStrict = True } ))
|
2007-07-22 21:20:21 +02:00
|
|
|
"" -- "Disable markdown syntax extensions"
|
2006-12-30 23:51:49 +01:00
|
|
|
|
2006-10-17 16:22:29 +02:00
|
|
|
, Option "R" ["parse-raw"]
|
|
|
|
(NoArg
|
|
|
|
(\opt -> return opt { optParseRaw = True }))
|
2006-12-31 02:12:01 +01:00
|
|
|
"" -- "Parse untranslatable HTML codes and LaTeX environments as raw"
|
2006-10-17 16:22:29 +02:00
|
|
|
|
2006-12-18 23:02:39 +01:00
|
|
|
, Option "S" ["smart"]
|
2006-10-17 16:22:29 +02:00
|
|
|
(NoArg
|
2006-12-18 23:02:39 +01:00
|
|
|
(\opt -> return opt { optSmart = True }))
|
2007-01-06 10:54:58 +01:00
|
|
|
"" -- "Use smart quotes, dashes, and ellipses"
|
2006-10-17 16:22:29 +02:00
|
|
|
|
2012-01-01 22:48:28 +01:00
|
|
|
, Option "" ["old-dashes"]
|
|
|
|
(NoArg
|
|
|
|
(\opt -> return opt { optSmart = True
|
|
|
|
, optOldDashes = True }))
|
|
|
|
"" -- "Use smart quotes, dashes, and ellipses"
|
|
|
|
|
2012-01-26 07:45:49 +01:00
|
|
|
, Option "" ["base-header-level"]
|
|
|
|
(ReqArg
|
|
|
|
(\arg opt ->
|
|
|
|
case reads arg of
|
|
|
|
[(t,"")] | t > 0 -> do
|
|
|
|
let oldTransforms = optTransforms opt
|
|
|
|
let shift = t - 1
|
|
|
|
return opt{ optTransforms =
|
|
|
|
headerShift shift : oldTransforms }
|
|
|
|
_ -> err 19
|
|
|
|
"base-header-level must be a number > 0")
|
|
|
|
"NUMBER")
|
|
|
|
"" -- "Headers base level"
|
|
|
|
|
|
|
|
, Option "" ["indented-code-classes"]
|
|
|
|
(ReqArg
|
|
|
|
(\arg opt -> return opt { optIndentedCodeClasses = words $
|
|
|
|
map (\c -> if c == ',' then ' ' else c) arg })
|
|
|
|
"STRING")
|
|
|
|
"" -- "Classes (whitespace- or comma-separated) to use for indented code-blocks"
|
|
|
|
|
|
|
|
, Option "" ["normalize"]
|
2011-01-12 05:37:06 +01:00
|
|
|
(NoArg
|
2012-01-26 07:45:49 +01:00
|
|
|
(\opt -> return opt { optTransforms =
|
|
|
|
normalize : optTransforms opt } ))
|
|
|
|
"" -- "Normalize the Pandoc AST"
|
|
|
|
|
|
|
|
, Option "p" ["preserve-tabs"]
|
|
|
|
(NoArg
|
|
|
|
(\opt -> return opt { optPreserveTabs = True }))
|
|
|
|
"" -- "Preserve tabs instead of converting to spaces"
|
|
|
|
|
|
|
|
, Option "" ["tab-stop"]
|
|
|
|
(ReqArg
|
|
|
|
(\arg opt ->
|
|
|
|
case reads arg of
|
|
|
|
[(t,"")] | t > 0 -> return opt { optTabStop = t }
|
|
|
|
_ -> err 31
|
|
|
|
"tab-stop must be a number greater than 0")
|
|
|
|
"NUMBER")
|
|
|
|
"" -- "Tab stop (default 4)"
|
|
|
|
|
|
|
|
, Option "s" ["standalone"]
|
|
|
|
(NoArg
|
|
|
|
(\opt -> return opt { optStandalone = True }))
|
|
|
|
"" -- "Include needed header and footer on output"
|
|
|
|
|
|
|
|
, Option "" ["template"]
|
|
|
|
(ReqArg
|
|
|
|
(\arg opt -> do
|
|
|
|
return opt{ optTemplate = Just arg,
|
|
|
|
optStandalone = True })
|
|
|
|
"FILENAME")
|
|
|
|
"" -- "Use custom template"
|
|
|
|
|
|
|
|
, Option "V" ["variable"]
|
|
|
|
(ReqArg
|
|
|
|
(\arg opt ->
|
|
|
|
case break (`elem` ":=") arg of
|
|
|
|
(k,_:v) -> do
|
|
|
|
let newvars = optVariables opt ++ [(k,v)]
|
|
|
|
return opt{ optVariables = newvars }
|
|
|
|
_ -> err 17 $
|
|
|
|
"Could not parse `" ++ arg ++ "' as a key/value pair (k=v or k:v)")
|
|
|
|
"KEY:VALUE")
|
|
|
|
"" -- "Use custom template"
|
|
|
|
|
|
|
|
, Option "D" ["print-default-template"]
|
|
|
|
(ReqArg
|
|
|
|
(\arg _ -> do
|
|
|
|
templ <- getDefaultTemplate Nothing arg
|
|
|
|
case templ of
|
|
|
|
Right t -> UTF8.hPutStr stdout t
|
|
|
|
Left e -> error $ show e
|
|
|
|
exitWith ExitSuccess)
|
|
|
|
"FORMAT")
|
|
|
|
"" -- "Print default template for FORMAT"
|
|
|
|
|
|
|
|
, Option "" ["no-wrap"]
|
|
|
|
(NoArg
|
|
|
|
(\opt -> return opt { optWrapText = False }))
|
|
|
|
"" -- "Do not wrap text in output"
|
|
|
|
|
|
|
|
, Option "" ["columns"]
|
|
|
|
(ReqArg
|
|
|
|
(\arg opt ->
|
|
|
|
case reads arg of
|
|
|
|
[(t,"")] | t > 0 -> return opt { optColumns = t }
|
|
|
|
_ -> err 33 $
|
|
|
|
"columns must be a number greater than 0")
|
|
|
|
"NUMBER")
|
|
|
|
"" -- "Length of line in characters"
|
|
|
|
|
|
|
|
, Option "" ["toc", "table-of-contents"]
|
|
|
|
(NoArg
|
|
|
|
(\opt -> return opt { optTableOfContents = True }))
|
|
|
|
"" -- "Include table of contents"
|
2011-01-12 05:37:06 +01:00
|
|
|
|
2011-12-28 08:46:23 +01:00
|
|
|
, Option "" ["no-highlight"]
|
|
|
|
(NoArg
|
|
|
|
(\opt -> return opt { optHighlight = False }))
|
|
|
|
"" -- "Don't highlight source code"
|
|
|
|
|
|
|
|
, Option "" ["highlight-style"]
|
|
|
|
(ReqArg
|
|
|
|
(\arg opt -> do
|
|
|
|
newStyle <- case map toLower arg of
|
|
|
|
"pygments" -> return pygments
|
|
|
|
"tango" -> return tango
|
|
|
|
"espresso" -> return espresso
|
|
|
|
"kate" -> return kate
|
|
|
|
"monochrome" -> return monochrome
|
|
|
|
"haddock" -> return haddock
|
2012-01-21 07:12:03 +01:00
|
|
|
_ -> err 39 $
|
|
|
|
"Unknown style :" ++ arg
|
2011-12-28 08:46:23 +01:00
|
|
|
return opt{ optHighlightStyle = newStyle })
|
|
|
|
"STYLE")
|
|
|
|
"" -- "Style for highlighted code"
|
|
|
|
|
2012-01-26 07:45:49 +01:00
|
|
|
, Option "H" ["include-in-header"]
|
|
|
|
(ReqArg
|
2010-07-16 04:01:00 +02:00
|
|
|
(\arg opt -> do
|
2012-01-26 07:45:49 +01:00
|
|
|
text <- UTF8.readFile arg
|
|
|
|
-- add new ones to end, so they're included in order specified
|
|
|
|
let newvars = optVariables opt ++ [("header-includes",text)]
|
|
|
|
return opt { optVariables = newvars,
|
|
|
|
optStandalone = True })
|
|
|
|
"FILENAME")
|
|
|
|
"" -- "File to include at end of header (implies -s)"
|
2007-12-01 04:11:52 +01:00
|
|
|
|
2012-01-26 07:45:49 +01:00
|
|
|
, Option "B" ["include-before-body"]
|
|
|
|
(ReqArg
|
2010-07-16 04:01:00 +02:00
|
|
|
(\arg opt -> do
|
2012-01-26 07:45:49 +01:00
|
|
|
text <- UTF8.readFile arg
|
|
|
|
-- add new ones to end, so they're included in order specified
|
|
|
|
let newvars = optVariables opt ++ [("include-before",text)]
|
|
|
|
return opt { optVariables = newvars,
|
|
|
|
optStandalone = True })
|
|
|
|
"FILENAME")
|
|
|
|
"" -- "File to include before document body"
|
2008-10-28 22:54:50 +01:00
|
|
|
|
2012-01-26 07:45:49 +01:00
|
|
|
, Option "A" ["include-after-body"]
|
|
|
|
(ReqArg
|
2011-07-23 22:30:59 +02:00
|
|
|
(\arg opt -> do
|
2012-01-26 07:45:49 +01:00
|
|
|
text <- UTF8.readFile arg
|
|
|
|
-- add new ones to end, so they're included in order specified
|
|
|
|
let newvars = optVariables opt ++ [("include-after",text)]
|
|
|
|
return opt { optVariables = newvars,
|
|
|
|
optStandalone = True })
|
|
|
|
"FILENAME")
|
|
|
|
"" -- "File to include after document body"
|
2007-12-01 04:11:52 +01:00
|
|
|
|
2012-01-26 07:45:49 +01:00
|
|
|
, Option "" ["self-contained"]
|
2006-10-17 16:22:29 +02:00
|
|
|
(NoArg
|
2012-01-26 07:45:49 +01:00
|
|
|
(\opt -> return opt { optSelfContained = True,
|
|
|
|
optVariables = ("slidy-url","slidy") :
|
|
|
|
optVariables opt,
|
|
|
|
optStandalone = True }))
|
|
|
|
"" -- "Make slide shows include all the needed js and css"
|
2006-10-17 16:22:29 +02:00
|
|
|
|
2010-07-23 06:50:17 +02:00
|
|
|
, Option "" ["offline"]
|
|
|
|
(NoArg
|
2012-01-21 18:55:37 +01:00
|
|
|
(\opt -> do warn $ "--offline is deprecated. Use --self-contained instead."
|
|
|
|
return opt { optSelfContained = True,
|
|
|
|
optStandalone = True }))
|
2011-11-22 00:24:28 +01:00
|
|
|
"" -- "Make slide shows include all the needed js and css"
|
|
|
|
-- deprecated synonym for --self-contained
|
|
|
|
|
2012-01-26 07:45:49 +01:00
|
|
|
, Option "5" ["html5"]
|
2011-11-22 00:24:28 +01:00
|
|
|
(NoArg
|
2012-01-26 07:45:49 +01:00
|
|
|
(\opt -> do
|
|
|
|
warn $ "--html5 is deprecated. "
|
|
|
|
++ "Use the html5 output format instead."
|
|
|
|
return opt { optHtml5 = True }))
|
|
|
|
"" -- "Produce HTML5 in HTML output"
|
|
|
|
|
2012-02-05 23:58:55 +01:00
|
|
|
, Option "" ["ascii"]
|
|
|
|
(NoArg
|
|
|
|
(\opt -> return opt { optAscii = True }))
|
|
|
|
"" -- "Use ascii characters only in HTML output"
|
|
|
|
|
2012-01-26 07:45:49 +01:00
|
|
|
, Option "" ["reference-links"]
|
|
|
|
(NoArg
|
|
|
|
(\opt -> return opt { optReferenceLinks = True } ))
|
|
|
|
"" -- "Use reference links in parsing HTML"
|
2010-07-23 06:50:17 +02:00
|
|
|
|
2012-01-27 08:55:37 +01:00
|
|
|
, Option "" ["atx-headers"]
|
|
|
|
(NoArg
|
|
|
|
(\opt -> return opt { optSetextHeaders = False } ))
|
|
|
|
"" -- "Use atx-style headers for markdown"
|
|
|
|
|
2011-01-16 18:34:26 +01:00
|
|
|
, Option "" ["chapters"]
|
|
|
|
(NoArg
|
|
|
|
(\opt -> return opt { optChapters = True }))
|
|
|
|
"" -- "Use chapter for top-level sections in LaTeX, DocBook"
|
|
|
|
|
2006-10-17 16:22:29 +02:00
|
|
|
, Option "N" ["number-sections"]
|
|
|
|
(NoArg
|
|
|
|
(\opt -> return opt { optNumberSections = True }))
|
2006-12-31 02:12:01 +01:00
|
|
|
"" -- "Number sections in LaTeX"
|
2006-10-17 16:22:29 +02:00
|
|
|
|
2011-01-17 23:54:51 +01:00
|
|
|
, Option "" ["listings"]
|
|
|
|
(NoArg
|
|
|
|
(\opt -> return opt { optListings = True }))
|
|
|
|
"" -- "Use listings package for LaTeX code blocks"
|
|
|
|
|
2012-01-26 07:45:49 +01:00
|
|
|
, Option "i" ["incremental"]
|
|
|
|
(NoArg
|
|
|
|
(\opt -> return opt { optIncremental = True }))
|
|
|
|
"" -- "Make list items display incrementally in Slidy/S5"
|
|
|
|
|
2012-01-26 02:50:03 +01:00
|
|
|
, Option "" ["slide-level"]
|
|
|
|
(ReqArg
|
|
|
|
(\arg opt -> do
|
|
|
|
case reads arg of
|
|
|
|
[(t,"")] | t >= 1 && t <= 6 ->
|
|
|
|
return opt { optSlideLevel = Just t }
|
|
|
|
_ -> err 39 $
|
|
|
|
"slide level must be a number between 1 and 6")
|
|
|
|
"NUMBER")
|
|
|
|
"" -- "Force header level for slides"
|
|
|
|
|
2010-07-16 04:01:00 +02:00
|
|
|
, Option "" ["section-divs"]
|
|
|
|
(NoArg
|
|
|
|
(\opt -> return opt { optSectionDivs = True }))
|
|
|
|
"" -- "Put sections in div tags in HTML"
|
|
|
|
|
2009-01-24 20:58:48 +01:00
|
|
|
, Option "" ["email-obfuscation"]
|
|
|
|
(ReqArg
|
|
|
|
(\arg opt -> do
|
|
|
|
method <- case arg of
|
|
|
|
"references" -> return ReferenceObfuscation
|
|
|
|
"javascript" -> return JavascriptObfuscation
|
|
|
|
"none" -> return NoObfuscation
|
2012-01-21 07:12:03 +01:00
|
|
|
_ -> err 6
|
2012-01-22 00:13:12 +01:00
|
|
|
("Unknown obfuscation method: " ++ arg)
|
2009-01-24 20:58:48 +01:00
|
|
|
return opt { optEmailObfuscation = method })
|
|
|
|
"none|javascript|references")
|
|
|
|
"" -- "Method for obfuscating email in HTML"
|
|
|
|
|
2009-12-05 18:56:02 +01:00
|
|
|
, Option "" ["id-prefix"]
|
|
|
|
(ReqArg
|
|
|
|
(\arg opt -> return opt { optIdentifierPrefix = arg })
|
|
|
|
"STRING")
|
|
|
|
"" -- "Prefix to add to automatically generated HTML identifiers"
|
|
|
|
|
2012-01-26 07:45:49 +01:00
|
|
|
, Option "T" ["title-prefix"]
|
2009-12-31 02:10:04 +01:00
|
|
|
(ReqArg
|
|
|
|
(\arg opt -> do
|
2012-01-26 07:45:49 +01:00
|
|
|
let newvars = ("title-prefix", arg) : optVariables opt
|
|
|
|
return opt { optVariables = newvars,
|
2009-12-31 02:10:04 +01:00
|
|
|
optStandalone = True })
|
2012-01-26 07:45:49 +01:00
|
|
|
"STRING")
|
|
|
|
"" -- "String to prefix to HTML window title"
|
2009-12-31 02:10:26 +01:00
|
|
|
|
2006-10-17 16:22:29 +02:00
|
|
|
, Option "c" ["css"]
|
|
|
|
(ReqArg
|
2008-08-10 19:33:20 +02:00
|
|
|
(\arg opt -> do
|
2009-12-31 02:15:50 +01:00
|
|
|
-- add new link to end, so it is included in proper order
|
|
|
|
let newvars = optVariables opt ++ [("css",arg)]
|
2009-12-31 02:10:32 +01:00
|
|
|
return opt { optVariables = newvars,
|
2008-01-08 21:21:28 +01:00
|
|
|
optStandalone = True })
|
2009-12-31 02:10:04 +01:00
|
|
|
"URL")
|
2006-12-31 02:12:01 +01:00
|
|
|
"" -- "Link to CSS style sheet"
|
2006-10-17 16:22:29 +02:00
|
|
|
|
2009-12-31 23:40:59 +01:00
|
|
|
, Option "" ["reference-odt"]
|
|
|
|
(ReqArg
|
|
|
|
(\arg opt -> do
|
|
|
|
return opt { optReferenceODT = Just arg })
|
|
|
|
"FILENAME")
|
|
|
|
"" -- "Path of custom reference.odt"
|
|
|
|
|
2012-01-03 21:10:10 +01:00
|
|
|
, Option "" ["reference-docx"]
|
|
|
|
(ReqArg
|
|
|
|
(\arg opt -> do
|
|
|
|
return opt { optReferenceDocx = Just arg })
|
|
|
|
"FILENAME")
|
|
|
|
"" -- "Path of custom reference.docx"
|
|
|
|
|
2010-07-03 07:07:00 +02:00
|
|
|
, Option "" ["epub-stylesheet"]
|
|
|
|
(ReqArg
|
|
|
|
(\arg opt -> do
|
|
|
|
text <- UTF8.readFile arg
|
|
|
|
return opt { optEPUBStylesheet = Just text })
|
|
|
|
"FILENAME")
|
|
|
|
"" -- "Path of epub.css"
|
|
|
|
|
2011-03-09 08:25:01 +01:00
|
|
|
, Option "" ["epub-cover-image"]
|
|
|
|
(ReqArg
|
|
|
|
(\arg opt ->
|
2011-04-16 18:53:11 +02:00
|
|
|
return opt { optVariables =
|
|
|
|
("epub-cover-image", arg) : optVariables opt })
|
2011-03-09 08:25:01 +01:00
|
|
|
"FILENAME")
|
|
|
|
"" -- "Path of epub cover image"
|
|
|
|
|
2010-07-05 01:56:17 +02:00
|
|
|
, Option "" ["epub-metadata"]
|
|
|
|
(ReqArg
|
|
|
|
(\arg opt -> do
|
|
|
|
text <- UTF8.readFile arg
|
|
|
|
return opt { optEPUBMetadata = text })
|
|
|
|
"FILENAME")
|
|
|
|
"" -- "Path of epub metadata file"
|
|
|
|
|
2012-01-30 20:45:55 +01:00
|
|
|
, Option "" ["epub-embed-font"]
|
|
|
|
(ReqArg
|
|
|
|
(\arg opt -> do
|
|
|
|
return opt{ optEPUBFonts = arg : optEPUBFonts opt })
|
|
|
|
"FILE")
|
|
|
|
"" -- "Directory of fonts to embed"
|
|
|
|
|
2012-01-21 23:46:27 +01:00
|
|
|
, Option "" ["latex-engine"]
|
2012-01-21 23:18:36 +01:00
|
|
|
(ReqArg
|
|
|
|
(\arg opt -> do
|
|
|
|
let b = takeBaseName arg
|
|
|
|
if (b == "pdflatex" || b == "lualatex" || b == "xelatex")
|
2012-01-21 23:46:27 +01:00
|
|
|
then return opt { optLaTeXEngine = arg }
|
|
|
|
else err 45 "latex-engine must be pdflatex, lualatex, or xelatex.")
|
2012-01-21 23:18:36 +01:00
|
|
|
"PROGRAM")
|
|
|
|
"" -- "Name of latex program to use in generating PDF"
|
|
|
|
|
2010-11-13 17:42:09 +01:00
|
|
|
, Option "" ["bibliography"]
|
2008-08-04 05:15:34 +02:00
|
|
|
(ReqArg
|
2010-12-13 21:18:01 +01:00
|
|
|
(\arg opt -> return opt { optBibliography = (optBibliography opt) ++ [arg] })
|
2008-08-04 05:15:34 +02:00
|
|
|
"FILENAME")
|
|
|
|
""
|
2011-01-16 20:08:20 +01:00
|
|
|
|
2008-08-04 05:15:34 +02:00
|
|
|
, Option "" ["csl"]
|
|
|
|
(ReqArg
|
2010-11-18 23:15:26 +01:00
|
|
|
(\arg opt -> return opt { optCslFile = arg })
|
2008-08-04 05:15:34 +02:00
|
|
|
"FILENAME")
|
|
|
|
""
|
2011-01-16 20:08:20 +01:00
|
|
|
|
2011-11-12 02:36:57 +01:00
|
|
|
, Option "" ["citation-abbreviations"]
|
|
|
|
(ReqArg
|
|
|
|
(\arg opt -> return opt { optAbbrevsFile = Just arg })
|
|
|
|
"FILENAME")
|
|
|
|
""
|
|
|
|
|
2011-01-16 20:08:37 +01:00
|
|
|
, Option "" ["natbib"]
|
2010-12-13 21:18:01 +01:00
|
|
|
(NoArg
|
|
|
|
(\opt -> return opt { optCiteMethod = Natbib }))
|
|
|
|
"" -- "Use natbib cite commands in LaTeX output"
|
2011-01-16 20:08:20 +01:00
|
|
|
|
2010-12-13 21:18:01 +01:00
|
|
|
, Option "" ["biblatex"]
|
|
|
|
(NoArg
|
|
|
|
(\opt -> return opt { optCiteMethod = Biblatex }))
|
|
|
|
"" -- "Use biblatex cite commands in LaTeX output"
|
2011-01-16 20:08:20 +01:00
|
|
|
|
2012-01-26 07:45:49 +01:00
|
|
|
, Option "m" ["latexmathml", "asciimathml"]
|
|
|
|
(OptArg
|
|
|
|
(\arg opt ->
|
|
|
|
return opt { optHTMLMathMethod = LaTeXMathML arg })
|
|
|
|
"URL")
|
|
|
|
"" -- "Use LaTeXMathML script in html output"
|
|
|
|
|
|
|
|
, Option "" ["mathml"]
|
|
|
|
(OptArg
|
|
|
|
(\arg opt ->
|
|
|
|
return opt { optHTMLMathMethod = MathML arg })
|
|
|
|
"URL")
|
|
|
|
"" -- "Use mathml for HTML math"
|
|
|
|
|
|
|
|
, Option "" ["mimetex"]
|
|
|
|
(OptArg
|
|
|
|
(\arg opt -> do
|
|
|
|
let url' = case arg of
|
|
|
|
Just u -> u ++ "?"
|
|
|
|
Nothing -> "/cgi-bin/mimetex.cgi?"
|
|
|
|
return opt { optHTMLMathMethod = WebTeX url' })
|
|
|
|
"URL")
|
|
|
|
"" -- "Use mimetex for HTML math"
|
|
|
|
|
|
|
|
, Option "" ["webtex"]
|
|
|
|
(OptArg
|
|
|
|
(\arg opt -> do
|
|
|
|
let url' = case arg of
|
|
|
|
Just u -> u
|
|
|
|
Nothing -> "http://chart.apis.google.com/chart?cht=tx&chl="
|
|
|
|
return opt { optHTMLMathMethod = WebTeX url' })
|
|
|
|
"URL")
|
|
|
|
"" -- "Use web service for HTML math"
|
|
|
|
|
|
|
|
, Option "" ["jsmath"]
|
|
|
|
(OptArg
|
|
|
|
(\arg opt -> return opt { optHTMLMathMethod = JsMath arg})
|
|
|
|
"URL")
|
|
|
|
"" -- "Use jsMath for HTML math"
|
|
|
|
|
|
|
|
, Option "" ["mathjax"]
|
|
|
|
(OptArg
|
|
|
|
(\arg opt -> do
|
|
|
|
let url' = case arg of
|
|
|
|
Just u -> u
|
|
|
|
Nothing -> "https://d3eoax9i5htok0.cloudfront.net/mathjax/latest/MathJax.js?config=TeX-AMS-MML_HTMLorMML"
|
|
|
|
return opt { optHTMLMathMethod = MathJax url'})
|
|
|
|
"URL")
|
|
|
|
"" -- "Use MathJax for HTML math"
|
|
|
|
|
|
|
|
, Option "" ["gladtex"]
|
|
|
|
(NoArg
|
|
|
|
(\opt -> return opt { optHTMLMathMethod = GladTeX }))
|
|
|
|
"" -- "Use gladtex for HTML math"
|
2010-01-14 06:54:38 +01:00
|
|
|
|
Changes to Pandoc's options to facilitate wrapper scripts:
+ removed -d/--debug option
+ added --dump-args option, which prints the name of the output file
(or '-' for STDOUT) and all the command-line arguments (excluding
Pandoc options and their arguments), one per line, then exits. Note
that special wrapper options will be treated as arguments if they
follow '--' at the end of the command line. Thus,
pandoc --dump-args -o foo.html foo.txt -- -e latin1
will print the following to STDOUT:
foo.html
foo.txt
-e
latin1
+ added --ignore-args option, which causes Pandoc to ignore all
(non-option) arguments, including any special options that occur
after '--' at the end of the command line.
+ '-' now means STDIN as the name of an input file, STDOUT as the
name of an output file. So,
pandoc -o - -
will take input from STDIN and print output to STDOUT. Note that
if multiple '-o' options are specified on the same line, the last
one takes precedence. So, in a script,
pandoc "$@" -o -
will guarantee output to STDOUT, even if the '-o' option was used.
+ documented these changes in man pages, README, and changelog.
git-svn-id: https://pandoc.googlecode.com/svn/trunk@454 788f1e2b-df1e-0410-8736-df70ead52e1b
2007-01-08 09:11:08 +01:00
|
|
|
, Option "" ["dump-args"]
|
2006-12-22 21:16:03 +01:00
|
|
|
(NoArg
|
Changes to Pandoc's options to facilitate wrapper scripts:
+ removed -d/--debug option
+ added --dump-args option, which prints the name of the output file
(or '-' for STDOUT) and all the command-line arguments (excluding
Pandoc options and their arguments), one per line, then exits. Note
that special wrapper options will be treated as arguments if they
follow '--' at the end of the command line. Thus,
pandoc --dump-args -o foo.html foo.txt -- -e latin1
will print the following to STDOUT:
foo.html
foo.txt
-e
latin1
+ added --ignore-args option, which causes Pandoc to ignore all
(non-option) arguments, including any special options that occur
after '--' at the end of the command line.
+ '-' now means STDIN as the name of an input file, STDOUT as the
name of an output file. So,
pandoc -o - -
will take input from STDIN and print output to STDOUT. Note that
if multiple '-o' options are specified on the same line, the last
one takes precedence. So, in a script,
pandoc "$@" -o -
will guarantee output to STDOUT, even if the '-o' option was used.
+ documented these changes in man pages, README, and changelog.
git-svn-id: https://pandoc.googlecode.com/svn/trunk@454 788f1e2b-df1e-0410-8736-df70ead52e1b
2007-01-08 09:11:08 +01:00
|
|
|
(\opt -> return opt { optDumpArgs = True }))
|
|
|
|
"" -- "Print output filename and arguments to stdout."
|
|
|
|
|
2008-08-04 05:15:34 +02:00
|
|
|
, Option "" ["ignore-args"]
|
Changes to Pandoc's options to facilitate wrapper scripts:
+ removed -d/--debug option
+ added --dump-args option, which prints the name of the output file
(or '-' for STDOUT) and all the command-line arguments (excluding
Pandoc options and their arguments), one per line, then exits. Note
that special wrapper options will be treated as arguments if they
follow '--' at the end of the command line. Thus,
pandoc --dump-args -o foo.html foo.txt -- -e latin1
will print the following to STDOUT:
foo.html
foo.txt
-e
latin1
+ added --ignore-args option, which causes Pandoc to ignore all
(non-option) arguments, including any special options that occur
after '--' at the end of the command line.
+ '-' now means STDIN as the name of an input file, STDOUT as the
name of an output file. So,
pandoc -o - -
will take input from STDIN and print output to STDOUT. Note that
if multiple '-o' options are specified on the same line, the last
one takes precedence. So, in a script,
pandoc "$@" -o -
will guarantee output to STDOUT, even if the '-o' option was used.
+ documented these changes in man pages, README, and changelog.
git-svn-id: https://pandoc.googlecode.com/svn/trunk@454 788f1e2b-df1e-0410-8736-df70ead52e1b
2007-01-08 09:11:08 +01:00
|
|
|
(NoArg
|
|
|
|
(\opt -> return opt { optIgnoreArgs = True }))
|
|
|
|
"" -- "Ignore command-line arguments."
|
2008-08-10 19:33:20 +02:00
|
|
|
|
2006-12-22 21:16:03 +01:00
|
|
|
, Option "v" ["version"]
|
|
|
|
(NoArg
|
|
|
|
(\_ -> do
|
|
|
|
prg <- getProgName
|
2010-05-07 05:29:44 +02:00
|
|
|
UTF8.hPutStrLn stdout (prg ++ " " ++ pandocVersion ++ compileInfo ++
|
2006-12-22 21:16:03 +01:00
|
|
|
copyrightMessage)
|
2009-02-26 17:47:36 +01:00
|
|
|
exitWith ExitSuccess ))
|
2006-12-31 02:12:01 +01:00
|
|
|
"" -- "Print version"
|
2006-12-22 21:16:03 +01:00
|
|
|
|
|
|
|
, Option "h" ["help"]
|
|
|
|
(NoArg
|
2006-12-28 03:20:09 +01:00
|
|
|
(\_ -> do
|
|
|
|
prg <- getProgName
|
2010-05-07 05:29:44 +02:00
|
|
|
UTF8.hPutStr stdout (usageMessage prg options)
|
2009-02-26 17:47:36 +01:00
|
|
|
exitWith ExitSuccess ))
|
2006-12-31 02:12:01 +01:00
|
|
|
"" -- "Show help"
|
2012-01-26 07:45:49 +01:00
|
|
|
|
2006-10-17 16:22:29 +02:00
|
|
|
]
|
2006-12-22 21:16:03 +01:00
|
|
|
|
2006-12-31 02:12:01 +01:00
|
|
|
-- Returns usage message
|
|
|
|
usageMessage :: String -> [OptDescr (Opt -> IO Opt)] -> String
|
2009-01-24 20:59:07 +01:00
|
|
|
usageMessage programName = usageInfo
|
2008-08-10 19:33:20 +02:00
|
|
|
(programName ++ " [OPTIONS] [FILES]" ++ "\nInput formats: " ++
|
2011-12-29 22:53:25 +01:00
|
|
|
(wrapWords 16 78 $ map fst readers) ++ "\nOutput formats: " ++
|
2012-01-03 21:10:10 +01:00
|
|
|
(wrapWords 16 78 $ map fst writers ++ nonTextFormats) ++ "\nOptions:")
|
2008-08-10 19:33:20 +02:00
|
|
|
|
2006-12-28 03:20:09 +01:00
|
|
|
-- Determine default reader based on source file extensions
|
2010-03-18 07:45:50 +01:00
|
|
|
defaultReaderName :: String -> [FilePath] -> String
|
|
|
|
defaultReaderName fallback [] = fallback
|
|
|
|
defaultReaderName fallback (x:xs) =
|
2008-02-09 04:21:04 +01:00
|
|
|
case takeExtension (map toLower x) of
|
|
|
|
".xhtml" -> "html"
|
|
|
|
".html" -> "html"
|
|
|
|
".htm" -> "html"
|
|
|
|
".tex" -> "latex"
|
|
|
|
".latex" -> "latex"
|
|
|
|
".ltx" -> "latex"
|
|
|
|
".rst" -> "rst"
|
2008-12-02 23:43:17 +01:00
|
|
|
".lhs" -> "markdown+lhs"
|
2010-12-04 07:15:51 +01:00
|
|
|
".textile" -> "textile"
|
2008-02-09 04:21:04 +01:00
|
|
|
".native" -> "native"
|
2010-12-13 05:30:26 +01:00
|
|
|
".json" -> "json"
|
2010-03-18 07:45:50 +01:00
|
|
|
_ -> defaultReaderName fallback xs
|
2006-12-28 03:20:09 +01:00
|
|
|
|
2008-12-02 23:41:51 +01:00
|
|
|
-- Returns True if extension of first source is .lhs
|
|
|
|
lhsExtension :: [FilePath] -> Bool
|
|
|
|
lhsExtension (x:_) = takeExtension x == ".lhs"
|
|
|
|
lhsExtension _ = False
|
|
|
|
|
2006-12-28 03:20:09 +01:00
|
|
|
-- Determine default writer based on output file extension
|
2008-02-09 04:21:04 +01:00
|
|
|
defaultWriterName :: FilePath -> String
|
Changes to Pandoc's options to facilitate wrapper scripts:
+ removed -d/--debug option
+ added --dump-args option, which prints the name of the output file
(or '-' for STDOUT) and all the command-line arguments (excluding
Pandoc options and their arguments), one per line, then exits. Note
that special wrapper options will be treated as arguments if they
follow '--' at the end of the command line. Thus,
pandoc --dump-args -o foo.html foo.txt -- -e latin1
will print the following to STDOUT:
foo.html
foo.txt
-e
latin1
+ added --ignore-args option, which causes Pandoc to ignore all
(non-option) arguments, including any special options that occur
after '--' at the end of the command line.
+ '-' now means STDIN as the name of an input file, STDOUT as the
name of an output file. So,
pandoc -o - -
will take input from STDIN and print output to STDOUT. Note that
if multiple '-o' options are specified on the same line, the last
one takes precedence. So, in a script,
pandoc "$@" -o -
will guarantee output to STDOUT, even if the '-o' option was used.
+ documented these changes in man pages, README, and changelog.
git-svn-id: https://pandoc.googlecode.com/svn/trunk@454 788f1e2b-df1e-0410-8736-df70ead52e1b
2007-01-08 09:11:08 +01:00
|
|
|
defaultWriterName "-" = "html" -- no output file
|
2006-12-28 03:20:09 +01:00
|
|
|
defaultWriterName x =
|
2008-02-09 04:21:04 +01:00
|
|
|
case takeExtension (map toLower x) of
|
2008-02-24 06:48:59 +01:00
|
|
|
"" -> "markdown" -- empty extension
|
|
|
|
".tex" -> "latex"
|
|
|
|
".latex" -> "latex"
|
|
|
|
".ltx" -> "latex"
|
|
|
|
".context" -> "context"
|
|
|
|
".ctx" -> "context"
|
|
|
|
".rtf" -> "rtf"
|
|
|
|
".rst" -> "rst"
|
|
|
|
".s5" -> "s5"
|
|
|
|
".native" -> "native"
|
2010-12-13 05:30:26 +01:00
|
|
|
".json" -> "json"
|
2008-02-24 06:48:59 +01:00
|
|
|
".txt" -> "markdown"
|
|
|
|
".text" -> "markdown"
|
|
|
|
".md" -> "markdown"
|
|
|
|
".markdown" -> "markdown"
|
2011-01-23 09:05:10 +01:00
|
|
|
".textile" -> "textile"
|
2008-12-02 23:43:17 +01:00
|
|
|
".lhs" -> "markdown+lhs"
|
2008-02-24 06:48:59 +01:00
|
|
|
".texi" -> "texinfo"
|
|
|
|
".texinfo" -> "texinfo"
|
|
|
|
".db" -> "docbook"
|
2008-08-01 01:16:02 +02:00
|
|
|
".odt" -> "odt"
|
2012-01-03 21:10:10 +01:00
|
|
|
".docx" -> "docx"
|
2010-07-03 07:07:00 +02:00
|
|
|
".epub" -> "epub"
|
2010-12-04 11:27:39 +01:00
|
|
|
".org" -> "org"
|
2011-11-16 23:52:10 +01:00
|
|
|
".asciidoc" -> "asciidoc"
|
2012-01-28 20:41:26 +01:00
|
|
|
".pdf" -> "latex"
|
2008-06-17 20:55:42 +02:00
|
|
|
['.',y] | y `elem` ['1'..'9'] -> "man"
|
2008-02-09 04:21:04 +01:00
|
|
|
_ -> "html"
|
2006-12-22 21:16:03 +01:00
|
|
|
|
2008-06-17 20:55:42 +02:00
|
|
|
main :: IO ()
|
2006-12-28 03:20:09 +01:00
|
|
|
main = do
|
2006-12-22 21:16:03 +01:00
|
|
|
|
2010-05-05 08:36:03 +02:00
|
|
|
rawArgs <- liftM (map decodeString) getArgs
|
2007-01-02 08:37:42 +01:00
|
|
|
prg <- getProgName
|
|
|
|
let compatMode = (prg == "hsmarkdown")
|
|
|
|
|
Changes to Pandoc's options to facilitate wrapper scripts:
+ removed -d/--debug option
+ added --dump-args option, which prints the name of the output file
(or '-' for STDOUT) and all the command-line arguments (excluding
Pandoc options and their arguments), one per line, then exits. Note
that special wrapper options will be treated as arguments if they
follow '--' at the end of the command line. Thus,
pandoc --dump-args -o foo.html foo.txt -- -e latin1
will print the following to STDOUT:
foo.html
foo.txt
-e
latin1
+ added --ignore-args option, which causes Pandoc to ignore all
(non-option) arguments, including any special options that occur
after '--' at the end of the command line.
+ '-' now means STDIN as the name of an input file, STDOUT as the
name of an output file. So,
pandoc -o - -
will take input from STDIN and print output to STDOUT. Note that
if multiple '-o' options are specified on the same line, the last
one takes precedence. So, in a script,
pandoc "$@" -o -
will guarantee output to STDOUT, even if the '-o' option was used.
+ documented these changes in man pages, README, and changelog.
git-svn-id: https://pandoc.googlecode.com/svn/trunk@454 788f1e2b-df1e-0410-8736-df70ead52e1b
2007-01-08 09:11:08 +01:00
|
|
|
let (actions, args, errors) = if compatMode
|
|
|
|
then ([], rawArgs, [])
|
|
|
|
else getOpt Permute options rawArgs
|
2006-12-22 21:16:03 +01:00
|
|
|
|
2009-01-24 20:59:07 +01:00
|
|
|
unless (null errors) $
|
2012-01-21 07:12:03 +01:00
|
|
|
err 2 $ concat $ errors ++
|
|
|
|
["Try " ++ prg ++ " --help for more information."]
|
2006-10-17 16:22:29 +02:00
|
|
|
|
2008-08-10 19:33:20 +02:00
|
|
|
let defaultOpts' = if compatMode
|
2007-01-02 08:37:42 +01:00
|
|
|
then defaultOpts { optReader = "markdown"
|
|
|
|
, optWriter = "html"
|
|
|
|
, optStrict = True }
|
|
|
|
else defaultOpts
|
|
|
|
|
2006-10-17 16:22:29 +02:00
|
|
|
-- thread option data structure through all supplied option actions
|
2007-01-02 08:37:42 +01:00
|
|
|
opts <- foldl (>>=) (return defaultOpts') actions
|
2006-10-17 16:22:29 +02:00
|
|
|
|
2009-04-08 22:19:50 +02:00
|
|
|
let Opt { optTabStop = tabStop
|
|
|
|
, optPreserveTabs = preserveTabs
|
2006-10-17 16:22:29 +02:00
|
|
|
, optStandalone = standalone
|
2006-12-28 03:20:09 +01:00
|
|
|
, optReader = readerName
|
|
|
|
, optWriter = writerName
|
2006-10-17 16:22:29 +02:00
|
|
|
, optParseRaw = parseRaw
|
2009-12-31 02:09:56 +01:00
|
|
|
, optVariables = variables
|
2007-07-07 07:43:23 +02:00
|
|
|
, optTableOfContents = toc
|
2010-03-18 07:45:28 +01:00
|
|
|
, optTransforms = transforms
|
2011-07-23 07:15:25 +02:00
|
|
|
, optTemplate = templatePath
|
2006-12-22 21:16:03 +01:00
|
|
|
, optOutputFile = outputFile
|
2006-10-17 16:22:29 +02:00
|
|
|
, optNumberSections = numberSections
|
2010-07-16 04:01:00 +02:00
|
|
|
, optSectionDivs = sectionDivs
|
2006-10-17 16:22:29 +02:00
|
|
|
, optIncremental = incremental
|
2011-11-22 00:24:28 +01:00
|
|
|
, optSelfContained = selfContained
|
2006-12-18 23:02:39 +01:00
|
|
|
, optSmart = smart
|
2012-01-01 22:48:28 +01:00
|
|
|
, optOldDashes = oldDashes
|
2011-01-12 05:37:06 +01:00
|
|
|
, optHtml5 = html5
|
2011-12-28 08:46:23 +01:00
|
|
|
, optHighlight = highlight
|
|
|
|
, optHighlightStyle = highlightStyle
|
2011-01-16 17:57:32 +01:00
|
|
|
, optChapters = chapters
|
2007-12-01 04:11:52 +01:00
|
|
|
, optHTMLMathMethod = mathMethod
|
2009-12-31 23:40:59 +01:00
|
|
|
, optReferenceODT = referenceODT
|
2012-01-03 21:10:10 +01:00
|
|
|
, optReferenceDocx = referenceDocx
|
2010-07-03 07:07:00 +02:00
|
|
|
, optEPUBStylesheet = epubStylesheet
|
2010-07-05 01:56:17 +02:00
|
|
|
, optEPUBMetadata = epubMetadata
|
2012-01-30 20:45:55 +01:00
|
|
|
, optEPUBFonts = epubFonts
|
Changes to Pandoc's options to facilitate wrapper scripts:
+ removed -d/--debug option
+ added --dump-args option, which prints the name of the output file
(or '-' for STDOUT) and all the command-line arguments (excluding
Pandoc options and their arguments), one per line, then exits. Note
that special wrapper options will be treated as arguments if they
follow '--' at the end of the command line. Thus,
pandoc --dump-args -o foo.html foo.txt -- -e latin1
will print the following to STDOUT:
foo.html
foo.txt
-e
latin1
+ added --ignore-args option, which causes Pandoc to ignore all
(non-option) arguments, including any special options that occur
after '--' at the end of the command line.
+ '-' now means STDIN as the name of an input file, STDOUT as the
name of an output file. So,
pandoc -o - -
will take input from STDIN and print output to STDOUT. Note that
if multiple '-o' options are specified on the same line, the last
one takes precedence. So, in a script,
pandoc "$@" -o -
will guarantee output to STDOUT, even if the '-o' option was used.
+ documented these changes in man pages, README, and changelog.
git-svn-id: https://pandoc.googlecode.com/svn/trunk@454 788f1e2b-df1e-0410-8736-df70ead52e1b
2007-01-08 09:11:08 +01:00
|
|
|
, optDumpArgs = dumpArgs
|
|
|
|
, optIgnoreArgs = ignoreArgs
|
2006-12-30 23:51:49 +01:00
|
|
|
, optStrict = strict
|
Extensive changes stemming from a rethinking of the Pandoc data
structure. Key and Note blocks have been removed. Link and image URLs
are now stored directly in Link and Image inlines, and note blocks
are stored in Note inlines. This requires changes in both parsers
and writers. Markdown and RST parsers need to extract data from key
and note blocks and insert them into the relevant inline elements.
Other parsers can be simplified, since there is no longer any need to
construct separate key and note blocks. Markdown, RST, and HTML writers
need to construct lists of notes; Markdown and RST writers need to
construct lists of link references (when the --reference-links option
is specified); and the RST writer needs to construct a list of image
substitution references. All writers have been rewritten to use the
State monad when state is required. This rewrite yields a small speed
boost and considerably cleaner code.
* Text/Pandoc/Definition.hs:
+ blocks: removed Key and Note
+ inlines: removed NoteRef, added Note
+ modified Target: there is no longer a 'Ref' target; all targets
are explicit URL, title pairs
* Text/Pandoc/Shared.hs:
+ Added 'Reference', 'isNoteBlock', 'isKeyBlock', 'isLineClump',
used in some of the readers.
+ Removed 'generateReference', 'keyTable', 'replaceReferenceLinks',
'replaceRefLinksBlockList', along with some auxiliary functions
used only by them. These are no longer needed, since
reference links are resolved in the Markdown and RST readers.
+ Moved 'inTags', 'selfClosingTag', 'inTagsSimple', and 'inTagsIndented'
to the Docbook writer, since that is now the only module that uses
them.
+ Changed name of 'escapeSGMLString' to 'escapeStringForXML'
+ Added KeyTable and NoteTable types
+ Removed fields from ParserState; 'stateKeyBlocks', 'stateKeysUsed',
'stateNoteBlocks', 'stateNoteIdentifiers', 'stateInlineLinks'.
Added 'stateKeys' and 'stateNotes'.
+ Added clause for Note to 'prettyBlock'.
+ Added 'writerNotes', 'writerReferenceLinks' fields to WriterOptions.
* Text/Pandoc/Entities.hs: Renamed 'escapeSGMLChar' and
'escapeSGMLString' to 'escapeCharForXML' and 'escapeStringForXML'
* Text/ParserCombinators/Pandoc.hs: Added lineClump parser: parses a raw
line block up to and including following blank lines.
* Main.hs: Replaced --inline-links with --reference-links.
* README:
+ Documented --reference-links and removed description of --inline-links.
+ Added note that footnotes may occur anywhere in the document, but must
be at the outer level, not embedded in block elements.
* man/man1/pandoc.1, man/man1/html2markdown.1: Removed --inline-links
option, added --reference-links option
* Markdown and RST readers:
+ Rewrote to fit new Pandoc definition. Since there are no longer
Note or Key blocks, all note and key blocks are parsed on a first pass
through the document. Once tables of notes and keys have been constructed,
the remaining parts of the document are reassembled and parsed.
+ Refactored link parsers.
* LaTeX and HTML readers: Rewrote to fit new Pandoc definition. Since
there are no longer Note or Key blocks, notes and references can be
parsed in a single pass through the document.
* RST, Markdown, and HTML writers: Rewrote using state monad new Pandoc
and definition. State is used to hold lists of references footnotes to
and be printed at the end of the document.
* RTF and LaTeX writers: Rewrote using new Pandoc definition. (Because
of the different treatment of footnotes, the "notes" parameter is no
longer needed in the block and inline conversion functions.)
* Docbook writer:
+ Moved the functions 'attributeList', 'inTags', 'selfClosingTag',
'inTagsSimple', 'inTagsIndented' from Text/Pandoc/Shared, since
they are now used only by the Docbook writer.
+ Rewrote using new Pandoc definition. (Because of the different
treatment of footnotes, the "notes" parameter is no longer needed
in the block and inline conversion functions.)
* Updated test suite
* Throughout: old haskell98 module names replaced by hierarchical module
names, e.g. List by Data.List.
* debian/control: Include libghc6-xhtml-dev instead of libghc6-html-dev
in "Build-Depends."
* cabalize:
+ Remove haskell98 from BASE_DEPENDS (since now the new hierarchical
module names are being used throughout)
+ Added mtl to BASE_DEPENDS (needed for state monad)
+ Removed html from GHC66_DEPENDS (not needed since xhtml is now used)
git-svn-id: https://pandoc.googlecode.com/svn/trunk@580 788f1e2b-df1e-0410-8736-df70ead52e1b
2007-04-10 03:56:50 +02:00
|
|
|
, optReferenceLinks = referenceLinks
|
2007-09-27 03:23:44 +02:00
|
|
|
, optWrapText = wrap
|
2010-12-13 05:09:14 +01:00
|
|
|
, optColumns = columns
|
2009-01-24 20:58:48 +01:00
|
|
|
, optEmailObfuscation = obfuscationMethod
|
2009-12-05 18:56:02 +01:00
|
|
|
, optIdentifierPrefix = idPrefix
|
2009-12-05 05:46:57 +01:00
|
|
|
, optIndentedCodeClasses = codeBlockClasses
|
2010-01-14 06:54:38 +01:00
|
|
|
, optDataDir = mbDataDir
|
2010-12-13 21:18:01 +01:00
|
|
|
, optBibliography = reffiles
|
2010-11-18 23:15:26 +01:00
|
|
|
, optCslFile = cslfile
|
2011-11-12 02:36:57 +01:00
|
|
|
, optAbbrevsFile = cslabbrevs
|
2010-12-13 21:18:01 +01:00
|
|
|
, optCiteMethod = citeMethod
|
2011-02-06 18:27:03 +01:00
|
|
|
, optListings = listings
|
2012-01-21 23:46:27 +01:00
|
|
|
, optLaTeXEngine = latexEngine
|
2012-01-26 02:50:03 +01:00
|
|
|
, optSlideLevel = slideLevel
|
2012-01-27 08:55:37 +01:00
|
|
|
, optSetextHeaders = setextHeaders
|
2012-02-05 23:58:55 +01:00
|
|
|
, optAscii = ascii
|
2006-10-17 16:22:29 +02:00
|
|
|
} = opts
|
|
|
|
|
2009-01-24 20:59:07 +01:00
|
|
|
when dumpArgs $
|
2010-05-07 05:29:44 +02:00
|
|
|
do UTF8.hPutStrLn stdout outputFile
|
|
|
|
mapM_ (\arg -> UTF8.hPutStrLn stdout arg) args
|
2009-01-24 20:59:07 +01:00
|
|
|
exitWith ExitSuccess
|
2007-01-09 02:43:23 +01:00
|
|
|
|
Changes to Pandoc's options to facilitate wrapper scripts:
+ removed -d/--debug option
+ added --dump-args option, which prints the name of the output file
(or '-' for STDOUT) and all the command-line arguments (excluding
Pandoc options and their arguments), one per line, then exits. Note
that special wrapper options will be treated as arguments if they
follow '--' at the end of the command line. Thus,
pandoc --dump-args -o foo.html foo.txt -- -e latin1
will print the following to STDOUT:
foo.html
foo.txt
-e
latin1
+ added --ignore-args option, which causes Pandoc to ignore all
(non-option) arguments, including any special options that occur
after '--' at the end of the command line.
+ '-' now means STDIN as the name of an input file, STDOUT as the
name of an output file. So,
pandoc -o - -
will take input from STDIN and print output to STDOUT. Note that
if multiple '-o' options are specified on the same line, the last
one takes precedence. So, in a script,
pandoc "$@" -o -
will guarantee output to STDOUT, even if the '-o' option was used.
+ documented these changes in man pages, README, and changelog.
git-svn-id: https://pandoc.googlecode.com/svn/trunk@454 788f1e2b-df1e-0410-8736-df70ead52e1b
2007-01-08 09:11:08 +01:00
|
|
|
let sources = if ignoreArgs then [] else args
|
|
|
|
|
2010-01-14 06:54:38 +01:00
|
|
|
datadir <- case mbDataDir of
|
2010-02-21 17:47:24 +01:00
|
|
|
Nothing -> catch
|
|
|
|
(liftM Just $ getAppUserDataDirectory "pandoc")
|
|
|
|
(const $ return Nothing)
|
|
|
|
Just _ -> return mbDataDir
|
2010-01-14 06:54:38 +01:00
|
|
|
|
2006-12-28 03:20:09 +01:00
|
|
|
-- assign reader and writer based on options and filenames
|
2008-08-10 19:33:20 +02:00
|
|
|
let readerName' = if null readerName
|
2010-03-18 07:45:50 +01:00
|
|
|
then let fallback = if any isURI sources
|
|
|
|
then "html"
|
|
|
|
else "markdown"
|
|
|
|
in defaultReaderName fallback sources
|
2011-11-22 23:21:19 +01:00
|
|
|
else readerName
|
2006-12-28 03:20:09 +01:00
|
|
|
|
2008-08-10 19:33:20 +02:00
|
|
|
let writerName' = if null writerName
|
2006-12-28 03:20:09 +01:00
|
|
|
then defaultWriterName outputFile
|
|
|
|
else writerName
|
|
|
|
|
2012-01-28 20:41:26 +01:00
|
|
|
let pdfOutput = map toLower (takeExtension outputFile) == ".pdf"
|
|
|
|
|
|
|
|
when pdfOutput $ do
|
|
|
|
-- make sure writer is latex or beamer
|
|
|
|
unless (writerName' == "latex" || writerName' == "beamer" ||
|
|
|
|
writerName' == "latex+lhs") $
|
|
|
|
err 47 $ "cannot produce pdf output with " ++ writerName' ++ " writer"
|
2012-01-21 18:34:47 +01:00
|
|
|
-- check for latex program
|
2012-01-21 23:46:27 +01:00
|
|
|
mbLatex <- findExecutable latexEngine
|
2012-01-21 18:34:47 +01:00
|
|
|
case mbLatex of
|
|
|
|
Nothing -> err 41 $
|
2012-01-21 23:46:27 +01:00
|
|
|
latexEngine ++ " not found. " ++
|
|
|
|
latexEngine ++ " is needed for pdf output."
|
2012-01-21 18:34:47 +01:00
|
|
|
Just _ -> return ()
|
|
|
|
|
2006-12-28 03:20:09 +01:00
|
|
|
reader <- case (lookup readerName' readers) of
|
|
|
|
Just r -> return r
|
2012-01-21 07:12:03 +01:00
|
|
|
Nothing -> err 7 ("Unknown reader: " ++ readerName')
|
2006-12-28 03:20:09 +01:00
|
|
|
|
2012-01-28 20:41:26 +01:00
|
|
|
let standalone' = standalone || writerName' `elem` nonTextFormats || pdfOutput
|
2011-11-22 23:21:19 +01:00
|
|
|
|
2011-07-23 07:15:25 +02:00
|
|
|
templ <- case templatePath of
|
2011-11-22 23:21:19 +01:00
|
|
|
_ | not standalone' -> return ""
|
2011-07-23 07:15:25 +02:00
|
|
|
Nothing -> do
|
|
|
|
deftemp <- getDefaultTemplate datadir writerName'
|
|
|
|
case deftemp of
|
|
|
|
Left e -> throwIO e
|
|
|
|
Right t -> return t
|
2011-07-23 07:49:38 +02:00
|
|
|
Just tp -> do
|
|
|
|
-- strip off "+lhs" if present
|
|
|
|
let format = takeWhile (/='+') writerName'
|
|
|
|
let tp' = case takeExtension tp of
|
|
|
|
"" -> tp <.> format
|
|
|
|
_ -> tp
|
|
|
|
catch (UTF8.readFile tp')
|
2011-07-23 07:15:25 +02:00
|
|
|
(\e -> if isDoesNotExistError e
|
|
|
|
then catch
|
2011-07-23 07:49:38 +02:00
|
|
|
(readDataFile datadir $
|
|
|
|
"templates" </> tp')
|
2011-07-23 07:15:25 +02:00
|
|
|
(\_ -> throwIO e)
|
|
|
|
else throwIO e)
|
2006-12-22 21:16:03 +01:00
|
|
|
|
2011-12-30 02:41:06 +01:00
|
|
|
let slideVariant = case writerName' of
|
|
|
|
"s5" -> S5Slides
|
|
|
|
"slidy" -> SlidySlides
|
|
|
|
"dzslides" -> DZSlides
|
|
|
|
_ -> NoSlides
|
|
|
|
|
2011-11-22 00:24:28 +01:00
|
|
|
variables' <- case mathMethod of
|
2009-12-31 02:13:26 +01:00
|
|
|
LaTeXMathML Nothing -> do
|
2010-03-18 07:45:56 +01:00
|
|
|
s <- readDataFile datadir $ "data" </> "LaTeXMathML.js"
|
2011-11-22 00:24:28 +01:00
|
|
|
return $ ("mathml-script", s) : variables
|
2010-03-18 07:45:56 +01:00
|
|
|
MathML Nothing -> do
|
|
|
|
s <- readDataFile datadir $ "data"</>"MathMLinHTML.js"
|
2011-11-22 00:24:28 +01:00
|
|
|
return $ ("mathml-script", s) : variables
|
|
|
|
_ -> return variables
|
2009-12-31 02:13:16 +01:00
|
|
|
|
2011-12-30 02:41:06 +01:00
|
|
|
variables'' <- case slideVariant of
|
|
|
|
DZSlides -> do
|
|
|
|
dztempl <- readDataFile datadir $ "dzslides" </> "template.html"
|
|
|
|
let dzcore = unlines $ dropWhile (not . isPrefixOf "<!-- {{{{ dzslides core")
|
|
|
|
$ lines dztempl
|
|
|
|
return $ ("dzslides-core", dzcore) : variables'
|
|
|
|
_ -> return variables'
|
|
|
|
|
2011-12-30 08:11:42 +01:00
|
|
|
-- unescape reference ids, which may contain XML entities, so
|
|
|
|
-- that we can do lookups with regular string equality
|
2012-02-05 23:37:33 +01:00
|
|
|
let unescapeRefId ref = ref{ refId = fromEntities (refId ref) }
|
2011-12-30 08:11:42 +01:00
|
|
|
|
2012-01-21 07:12:03 +01:00
|
|
|
refs <- mapM (\f -> catch (CSL.readBiblioFile f) $ \e ->
|
|
|
|
err 23 $ "Error reading bibliography `" ++ f ++ "'" ++ "\n" ++ show e)
|
|
|
|
reffiles >>=
|
2011-12-30 08:11:42 +01:00
|
|
|
return . map unescapeRefId . concat
|
2010-12-13 21:18:01 +01:00
|
|
|
|
2010-07-09 02:14:03 +02:00
|
|
|
let sourceDir = if null sources
|
|
|
|
then "."
|
|
|
|
else takeDirectory (head sources)
|
|
|
|
|
2008-08-10 19:33:20 +02:00
|
|
|
let startParserState =
|
2008-12-02 23:41:51 +01:00
|
|
|
defaultParserState { stateParseRaw = parseRaw,
|
|
|
|
stateTabStop = tabStop,
|
2008-12-02 23:43:17 +01:00
|
|
|
stateLiterateHaskell = "+lhs" `isSuffixOf` readerName' ||
|
2008-12-02 23:41:51 +01:00
|
|
|
lhsExtension sources,
|
|
|
|
stateStandalone = standalone',
|
2011-12-28 08:46:23 +01:00
|
|
|
stateCitations = map CSL.refId refs,
|
2008-12-02 23:41:51 +01:00
|
|
|
stateSmart = smart || writerName' `elem`
|
2012-01-28 20:41:26 +01:00
|
|
|
["latex", "context", "latex+lhs", "beamer"],
|
2012-01-01 22:48:28 +01:00
|
|
|
stateOldDashes = oldDashes,
|
2008-12-02 23:41:51 +01:00
|
|
|
stateColumns = columns,
|
2009-12-01 07:56:47 +01:00
|
|
|
stateStrict = strict,
|
2010-10-26 18:03:03 +02:00
|
|
|
stateIndentedCodeClasses = codeBlockClasses,
|
2011-12-29 22:58:13 +01:00
|
|
|
stateApplyMacros = writerName' `notElem`
|
2012-01-28 20:41:26 +01:00
|
|
|
["latex", "latex+lhs", "beamer"] }
|
2010-07-09 02:14:03 +02:00
|
|
|
|
2011-07-22 22:11:46 +02:00
|
|
|
let writerOptions = defaultWriterOptions
|
|
|
|
{ writerStandalone = standalone',
|
2011-07-23 07:15:25 +02:00
|
|
|
writerTemplate = templ,
|
2011-12-30 02:41:06 +01:00
|
|
|
writerVariables = variables'',
|
2010-07-05 01:56:17 +02:00
|
|
|
writerEPUBMetadata = epubMetadata,
|
2009-01-24 20:58:48 +01:00
|
|
|
writerTabStop = tabStop,
|
|
|
|
writerTableOfContents = toc &&
|
|
|
|
writerName' /= "s5",
|
|
|
|
writerHTMLMathMethod = mathMethod,
|
2010-07-14 05:44:56 +02:00
|
|
|
writerSlideVariant = slideVariant,
|
|
|
|
writerIncremental = incremental,
|
2010-12-13 21:18:01 +01:00
|
|
|
writerCiteMethod = citeMethod,
|
2010-12-15 11:40:53 +01:00
|
|
|
writerBiblioFiles = reffiles,
|
2009-01-24 20:58:48 +01:00
|
|
|
writerIgnoreNotes = False,
|
|
|
|
writerNumberSections = numberSections,
|
2010-07-16 04:01:00 +02:00
|
|
|
writerSectionDivs = sectionDivs,
|
2009-01-24 20:58:48 +01:00
|
|
|
writerStrictMarkdown = strict,
|
|
|
|
writerReferenceLinks = referenceLinks,
|
|
|
|
writerWrapText = wrap,
|
2010-12-13 05:09:14 +01:00
|
|
|
writerColumns = columns,
|
2009-01-24 20:58:48 +01:00
|
|
|
writerLiterateHaskell = "+lhs" `isSuffixOf` writerName' ||
|
|
|
|
lhsExtension [outputFile],
|
|
|
|
writerEmailObfuscation = if strict
|
|
|
|
then ReferenceObfuscation
|
2009-12-05 18:56:02 +01:00
|
|
|
else obfuscationMethod,
|
2010-07-09 02:14:03 +02:00
|
|
|
writerIdentifierPrefix = idPrefix,
|
2010-07-09 02:31:55 +02:00
|
|
|
writerSourceDirectory = sourceDir,
|
2011-01-12 05:37:06 +01:00
|
|
|
writerUserDataDir = datadir,
|
2011-10-02 07:57:03 +02:00
|
|
|
writerHtml5 = html5 ||
|
|
|
|
slideVariant == DZSlides,
|
2011-12-16 06:17:32 +01:00
|
|
|
writerChapters = chapters,
|
2011-12-22 22:12:08 +01:00
|
|
|
writerListings = listings,
|
2012-01-28 20:41:26 +01:00
|
|
|
writerBeamer = writerName' == "beamer",
|
2012-01-26 02:50:03 +01:00
|
|
|
writerSlideLevel = slideLevel,
|
2011-12-28 08:46:23 +01:00
|
|
|
writerHighlight = highlight,
|
2012-01-27 08:55:37 +01:00
|
|
|
writerHighlightStyle = highlightStyle,
|
|
|
|
writerSetextHeaders = setextHeaders
|
|
|
|
}
|
2006-10-17 16:22:29 +02:00
|
|
|
|
2012-01-03 21:10:10 +01:00
|
|
|
when (writerName' `elem` nonTextFormats&& outputFile == "-") $
|
2012-01-22 00:13:12 +01:00
|
|
|
err 5 $ "Cannot write " ++ writerName' ++ " output to stdout.\n" ++
|
2012-01-21 07:12:03 +01:00
|
|
|
"Specify an output file using the -o option."
|
2008-08-10 19:33:20 +02:00
|
|
|
|
2009-01-24 20:58:06 +01:00
|
|
|
let readSources [] = mapM readSource ["-"]
|
|
|
|
readSources srcs = mapM readSource srcs
|
2010-05-07 05:29:44 +02:00
|
|
|
readSource "-" = UTF8.getContents
|
2010-02-02 08:37:01 +01:00
|
|
|
readSource src = case parseURI src of
|
2010-11-13 03:30:50 +01:00
|
|
|
Just u | uriScheme u `elem` ["http:","https:"] ->
|
|
|
|
readURI u
|
|
|
|
_ -> UTF8.readFile src
|
2010-02-02 08:37:01 +01:00
|
|
|
readURI uri = simpleHTTP (mkRequest GET uri) >>= getResponseBody >>=
|
|
|
|
return . toString -- treat all as UTF8
|
2009-01-24 20:58:06 +01:00
|
|
|
|
2009-04-08 22:19:50 +02:00
|
|
|
let convertTabs = tabFilter (if preserveTabs then 0 else tabStop)
|
|
|
|
|
2012-01-30 08:54:00 +01:00
|
|
|
let handleIncludes' = if readerName' == "latex" || readerName' == "beamer" ||
|
|
|
|
readerName' == "latex+lhs" ||
|
|
|
|
readerName' == "context"
|
|
|
|
then handleIncludes
|
|
|
|
else return
|
|
|
|
|
|
|
|
doc <- (reader startParserState) `fmap` (readSources sources >>=
|
|
|
|
handleIncludes' . convertTabs . intercalate "\n")
|
2008-08-01 01:16:02 +02:00
|
|
|
|
2011-01-28 17:42:04 +01:00
|
|
|
let doc0 = foldr ($) doc transforms
|
2010-03-15 00:23:26 +01:00
|
|
|
|
2011-01-28 17:42:04 +01:00
|
|
|
doc1 <- if writerName' == "rtf"
|
|
|
|
then bottomUpM rtfEmbedImage doc0
|
|
|
|
else return doc0
|
|
|
|
|
|
|
|
doc2 <- do
|
2010-12-13 21:18:01 +01:00
|
|
|
if citeMethod == Citeproc && not (null refs)
|
|
|
|
then do
|
2010-11-24 06:40:05 +01:00
|
|
|
csldir <- getAppUserDataDirectory "csl"
|
2010-11-20 17:11:30 +01:00
|
|
|
cslfile' <- if null cslfile
|
|
|
|
then findDataFile datadir "default.csl"
|
2010-11-24 06:40:05 +01:00
|
|
|
else do
|
|
|
|
ex <- doesFileExist cslfile
|
|
|
|
if ex
|
|
|
|
then return cslfile
|
|
|
|
else findDataFile datadir $
|
|
|
|
replaceDirectory
|
|
|
|
(replaceExtension cslfile "csl")
|
|
|
|
csldir
|
2011-11-12 02:36:57 +01:00
|
|
|
processBiblio cslfile' cslabbrevs refs doc1
|
2011-01-28 17:42:04 +01:00
|
|
|
else return doc1
|
2006-10-17 16:22:29 +02:00
|
|
|
|
2012-01-28 20:41:26 +01:00
|
|
|
let writeBinary :: B.ByteString -> IO ()
|
|
|
|
writeBinary = B.writeFile (encodeString outputFile)
|
|
|
|
|
|
|
|
let writerFn :: FilePath -> String -> IO ()
|
|
|
|
writerFn "-" = UTF8.putStr
|
|
|
|
writerFn f = UTF8.writeFile f
|
|
|
|
|
2011-01-30 19:29:10 +01:00
|
|
|
case lookup writerName' writers of
|
2012-01-28 20:41:26 +01:00
|
|
|
Nothing
|
|
|
|
| writerName' == "epub" ->
|
2012-01-30 20:45:55 +01:00
|
|
|
writeEPUB epubStylesheet epubFonts writerOptions doc2
|
|
|
|
>>= writeBinary
|
2012-01-28 20:41:26 +01:00
|
|
|
| writerName' == "odt" ->
|
|
|
|
writeODT referenceODT writerOptions doc2 >>= writeBinary
|
|
|
|
| writerName' == "docx" ->
|
|
|
|
writeDocx referenceDocx writerOptions doc2 >>= writeBinary
|
|
|
|
| otherwise -> err 9 ("Unknown writer: " ++ writerName')
|
|
|
|
Just _
|
|
|
|
| pdfOutput -> do
|
|
|
|
res <- tex2pdf latexEngine $ writeLaTeX writerOptions doc2
|
2012-01-21 18:34:47 +01:00
|
|
|
case res of
|
|
|
|
Right pdf -> writeBinary pdf
|
|
|
|
Left err' -> err 43 $ toString err'
|
2012-02-05 23:58:55 +01:00
|
|
|
Just r
|
|
|
|
| htmlFormat && ascii ->
|
|
|
|
writerFn outputFile =<< selfcontain (toEntities result)
|
|
|
|
| otherwise ->
|
|
|
|
writerFn outputFile =<< selfcontain result
|
2012-01-28 20:41:26 +01:00
|
|
|
where result = r writerOptions doc2 ++ ['\n' | not standalone']
|
2012-02-05 23:58:55 +01:00
|
|
|
htmlFormat = writerName' `elem`
|
|
|
|
["html","html+lhs","html5","html5+lhs",
|
2012-02-05 18:58:16 +01:00
|
|
|
"s5","slidy","dzslides"]
|
2012-02-05 23:58:55 +01:00
|
|
|
selfcontain = if selfContained && htmlFormat
|
|
|
|
then makeSelfContained datadir
|
|
|
|
else return
|