2016-09-27 10:00:04 -04:00
|
|
|
{-# LANGUAGE CPP, TupleSections, ScopedTypeVariables, PatternGuards #-}
|
2006-12-20 20:54:23 +00:00
|
|
|
{-
|
2016-03-22 17:17:21 -07:00
|
|
|
Copyright (C) 2006-2016 John MacFarlane <jgm@berkeley.edu>
|
2006-12-20 20:54:23 +00: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 06:50:14 +00:00
|
|
|
{- |
|
|
|
|
Module : Main
|
2016-03-22 17:17:21 -07:00
|
|
|
Copyright : Copyright (C) 2006-2016 John MacFarlane
|
2008-08-10 17:33:20 +00:00
|
|
|
License : GNU GPL, version 2 or above
|
2006-12-20 06:50:14 +00:00
|
|
|
|
2007-07-07 22:51:55 +00:00
|
|
|
Maintainer : John MacFarlane <jgm@berkeley@edu>
|
2008-08-10 17:33:20 +00:00
|
|
|
Stability : alpha
|
2006-12-20 06:50:14 +00:00
|
|
|
Portability : portable
|
|
|
|
|
|
|
|
Parses command-line options and calls the appropriate readers and
|
|
|
|
writers.
|
|
|
|
-}
|
2006-10-17 14:22:29 +00:00
|
|
|
module Main where
|
2017-02-05 21:58:45 +01:00
|
|
|
import Text.Pandoc.App (defaultOpts, convertWithOpts, Opt(..))
|
2007-07-12 08:31:05 +00:00
|
|
|
import Text.Pandoc
|
2017-02-05 21:58:45 +01:00
|
|
|
import Text.Pandoc.Shared
|
|
|
|
import Text.Pandoc.Class (PandocIO)
|
|
|
|
import Text.Pandoc.Highlighting (highlightingStyles)
|
|
|
|
import Skylighting (Syntax(..), defaultSyntaxMap)
|
|
|
|
import Data.List (sort, intercalate)
|
|
|
|
import Data.Char (toUpper)
|
2006-10-17 14:22:29 +00:00
|
|
|
import System.Console.GetOpt
|
2017-02-05 21:58:45 +01:00
|
|
|
import Control.Monad
|
2010-05-06 20:29:44 -07:00
|
|
|
import qualified Text.Pandoc.UTF8 as UTF8
|
2017-02-05 21:58:45 +01:00
|
|
|
import System.Environment
|
|
|
|
import System.FilePath (takeBaseName)
|
|
|
|
import Data.Maybe (fromMaybe)
|
|
|
|
import qualified Data.Text as T
|
|
|
|
import qualified Control.Exception as E
|
2013-08-13 18:25:20 -07:00
|
|
|
import qualified Data.ByteString as BS
|
2013-09-17 21:04:27 -07:00
|
|
|
import qualified Data.Map as M
|
2017-02-05 21:58:45 +01:00
|
|
|
import System.Exit
|
|
|
|
import System.IO (stdout)
|
2015-10-14 09:09:10 -07:00
|
|
|
import Control.Applicative ((<|>))
|
2017-02-05 21:58:45 +01:00
|
|
|
import System.Directory (getAppUserDataDirectory)
|
2015-08-13 15:24:50 -07:00
|
|
|
import Paths_pandoc (getDataDir)
|
|
|
|
import Text.Printf (printf)
|
2015-02-18 19:57:30 +00:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
main :: IO ()
|
|
|
|
main = do
|
2014-07-31 16:26:48 -07:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
rawArgs <- map UTF8.decodeArg <$> getArgs
|
|
|
|
prg <- getProgName
|
2006-12-22 20:16:03 +00:00
|
|
|
|
2017-02-04 09:41:08 +01:00
|
|
|
let (actions, args, unrecognizedOpts, errors) =
|
|
|
|
getOpt' Permute options rawArgs
|
2008-02-09 03:22:01 +00:00
|
|
|
|
2017-02-04 09:41:08 +01:00
|
|
|
let unknownOptionErrors = foldr addDeprecationNote [] unrecognizedOpts
|
|
|
|
|
|
|
|
unless (null errors && null unknownOptionErrors) $
|
|
|
|
err 2 $ concat errors ++ unlines unknownOptionErrors ++
|
|
|
|
("Try " ++ prg ++ " --help for more information.")
|
2008-02-09 03:21:19 +00:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
-- thread option data structure through all supplied option actions
|
|
|
|
opts <- foldl (>>=) (return defaultOpts) actions
|
|
|
|
convertWithOpts opts args
|
2008-07-31 23:16:02 +00:00
|
|
|
|
2016-12-10 12:36: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 =
|
|
|
|
[ Option "fr" ["from","read"]
|
2016-10-11 15:07:10 -04:00
|
|
|
(ReqArg
|
2017-02-05 18:10:43 +01:00
|
|
|
(\arg opt -> return opt { optReader = Just arg })
|
2016-12-10 12:36:09 +01:00
|
|
|
"FORMAT")
|
|
|
|
""
|
2012-01-26 23:55:37 -08:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "tw" ["to","write"]
|
2016-10-19 13:12:57 +02:00
|
|
|
(ReqArg
|
2017-02-05 18:10:43 +01:00
|
|
|
(\arg opt -> return opt { optWriter = Just arg })
|
2016-12-10 12:36:09 +01:00
|
|
|
"FORMAT")
|
|
|
|
""
|
2016-09-06 21:43:45 +02:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "o" ["output"]
|
|
|
|
(ReqArg
|
|
|
|
(\arg opt -> return opt { optOutputFile = arg })
|
|
|
|
"FILENAME")
|
|
|
|
"" -- "Name of output file"
|
2006-10-17 14:22:29 +00:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "" ["data-dir"]
|
2013-02-21 21:40:06 -08:00
|
|
|
(ReqArg
|
2016-12-10 12:36:09 +01:00
|
|
|
(\arg opt -> return opt { optDataDir = Just arg })
|
|
|
|
"DIRECTORY") -- "Directory containing pandoc data files."
|
|
|
|
""
|
2013-02-21 21:40:06 -08:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "R" ["parse-raw"]
|
2012-05-11 22:58:49 -07:00
|
|
|
(NoArg
|
2016-12-10 12:36:09 +01:00
|
|
|
(\opt -> return opt { optParseRaw = True }))
|
|
|
|
"" -- "Parse untranslatable HTML codes and LaTeX environments as raw"
|
2012-05-11 22:58:49 -07:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "" ["base-header-level"]
|
2012-01-25 17:50:03 -08:00
|
|
|
(ReqArg
|
2015-11-21 22:45:25 -08:00
|
|
|
(\arg opt ->
|
2012-08-09 08:11:28 -07:00
|
|
|
case safeRead arg of
|
2017-02-04 10:09:20 +01:00
|
|
|
Just t | t > 0 && t < 6 -> do
|
|
|
|
return opt{ optBaseHeaderLevel = t }
|
2016-12-10 12:36:09 +01:00
|
|
|
_ -> err 19
|
2017-02-04 10:09:20 +01:00
|
|
|
"base-header-level must be 1-5")
|
2016-12-10 12:36:09 +01:00
|
|
|
"NUMBER")
|
|
|
|
"" -- "Headers base level"
|
2009-01-24 19:58:48 +00:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "" ["indented-code-classes"]
|
2009-12-05 17:56:02 +00:00
|
|
|
(ReqArg
|
2016-12-10 12:36:09 +01:00
|
|
|
(\arg opt -> return opt { optIndentedCodeClasses = words $
|
|
|
|
map (\c -> if c == ',' then ' ' else c) arg })
|
2009-12-05 17:56:02 +00:00
|
|
|
"STRING")
|
2016-12-10 12:36:09 +01:00
|
|
|
"" -- "Classes (whitespace- or comma-separated) to use for indented code-blocks"
|
2013-01-04 22:29:41 -08:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "F" ["filter"]
|
2012-01-21 14:18:36 -08:00
|
|
|
(ReqArg
|
2016-12-10 12:36:09 +01:00
|
|
|
(\arg opt -> return opt { optFilters = arg : optFilters opt })
|
2012-01-21 14:18:36 -08:00
|
|
|
"PROGRAM")
|
2016-12-10 12:36:09 +01:00
|
|
|
"" -- "External JSON filter"
|
2015-03-04 15:25:56 +05:30
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "p" ["preserve-tabs"]
|
|
|
|
(NoArg
|
|
|
|
(\opt -> return opt { optPreserveTabs = True }))
|
|
|
|
"" -- "Preserve tabs instead of converting to spaces"
|
2011-01-16 11:08:20 -08:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "" ["tab-stop"]
|
2011-11-11 17:36:57 -08:00
|
|
|
(ReqArg
|
2013-09-01 15:54:48 -07:00
|
|
|
(\arg opt ->
|
2016-12-10 12:36:09 +01:00
|
|
|
case safeRead arg of
|
|
|
|
Just t | t > 0 -> return opt { optTabStop = t }
|
|
|
|
_ -> err 31
|
|
|
|
"tab-stop must be a number greater than 0")
|
|
|
|
"NUMBER")
|
|
|
|
"" -- "Tab stop (default 4)"
|
2011-11-11 17:36:57 -08:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "" ["track-changes"]
|
|
|
|
(ReqArg
|
|
|
|
(\arg opt -> do
|
|
|
|
action <- case arg of
|
|
|
|
"accept" -> return AcceptChanges
|
|
|
|
"reject" -> return RejectChanges
|
|
|
|
"all" -> return AllChanges
|
|
|
|
_ -> err 6
|
|
|
|
("Unknown option for track-changes: " ++ arg)
|
|
|
|
return opt { optTrackChanges = action })
|
|
|
|
"accept|reject|all")
|
|
|
|
"" -- "Accepting or reject MS Word track-changes.""
|
2011-01-16 11:08:20 -08:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "" ["file-scope"]
|
2010-12-13 21:18:01 +01:00
|
|
|
(NoArg
|
2016-12-10 12:36:09 +01:00
|
|
|
(\opt -> return opt { optFileScope = True }))
|
|
|
|
"" -- "Parse input files before combining"
|
2011-01-16 11:08:20 -08:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "" ["extract-media"]
|
|
|
|
(ReqArg
|
2012-01-25 22:45:49 -08:00
|
|
|
(\arg opt ->
|
2016-12-10 12:36:09 +01:00
|
|
|
return opt { optExtractMedia = Just arg })
|
|
|
|
"PATH")
|
|
|
|
"" -- "Directory to which to extract embedded media"
|
2012-01-25 22:45:49 -08:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "s" ["standalone"]
|
|
|
|
(NoArg
|
|
|
|
(\opt -> return opt { optStandalone = True }))
|
|
|
|
"" -- "Include needed header and footer on output"
|
|
|
|
|
|
|
|
, Option "" ["template"]
|
|
|
|
(ReqArg
|
2012-01-25 22:45:49 -08:00
|
|
|
(\arg opt ->
|
2016-12-10 12:36:09 +01:00
|
|
|
return opt{ optTemplate = Just arg,
|
|
|
|
optStandalone = True })
|
|
|
|
"FILENAME")
|
|
|
|
"" -- "Use custom template"
|
2012-01-25 22:45:49 -08:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "M" ["metadata"]
|
|
|
|
(ReqArg
|
2012-01-25 22:45:49 -08:00
|
|
|
(\arg opt -> do
|
2017-02-05 21:58:45 +01:00
|
|
|
let (key, val) = splitField arg
|
|
|
|
return opt{ optMetadata = (key, val) : optMetadata opt })
|
2016-12-10 12:36:09 +01:00
|
|
|
"KEY[:VALUE]")
|
|
|
|
""
|
2012-01-25 22:45:49 -08:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "V" ["variable"]
|
|
|
|
(ReqArg
|
2012-01-25 22:45:49 -08:00
|
|
|
(\arg opt -> do
|
2017-02-05 21:58:45 +01:00
|
|
|
let (key, val) = splitField arg
|
|
|
|
return opt{ optVariables = (key, val) : optVariables opt })
|
2016-12-10 12:36:09 +01:00
|
|
|
"KEY[:VALUE]")
|
|
|
|
""
|
2012-01-25 22:45:49 -08:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, 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
|
|
|
|
exitSuccess)
|
|
|
|
"FORMAT")
|
|
|
|
"" -- "Print default template for FORMAT"
|
2012-01-25 22:45:49 -08:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "" ["print-default-data-file"]
|
|
|
|
(ReqArg
|
|
|
|
(\arg _ -> do
|
|
|
|
readDataFile Nothing arg >>= BS.hPutStr stdout
|
|
|
|
exitSuccess)
|
|
|
|
"FILE")
|
|
|
|
"" -- "Print default data file"
|
|
|
|
|
|
|
|
, Option "" ["dpi"]
|
|
|
|
(ReqArg
|
2014-09-25 18:23:28 +01:00
|
|
|
(\arg opt ->
|
2016-12-10 12:36:09 +01:00
|
|
|
case safeRead arg of
|
|
|
|
Just t | t > 0 -> return opt { optDpi = t }
|
|
|
|
_ -> err 31
|
|
|
|
"dpi must be a number greater than 0")
|
|
|
|
"NUMBER")
|
|
|
|
"" -- "Dpi (default 96)"
|
2014-09-25 18:23:28 +01:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "" ["wrap"]
|
2014-09-25 18:23:28 +01:00
|
|
|
(ReqArg
|
|
|
|
(\arg opt ->
|
2016-12-10 12:36:09 +01:00
|
|
|
case safeRead ("Wrap" ++ uppercaseFirstLetter arg) of
|
|
|
|
Just o -> return opt { optWrapText = o }
|
|
|
|
Nothing -> err 77 "--wrap must be auto, none, or preserve")
|
|
|
|
"auto|none|preserve")
|
|
|
|
"" -- "Option for wrapping text in output"
|
2012-01-25 22:45:49 -08:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "" ["columns"]
|
|
|
|
(ReqArg
|
|
|
|
(\arg opt ->
|
|
|
|
case safeRead arg of
|
|
|
|
Just t | t > 0 -> return opt { optColumns = t }
|
|
|
|
_ -> err 33
|
|
|
|
"columns must be a number greater than 0")
|
|
|
|
"NUMBER")
|
|
|
|
"" -- "Length of line in characters"
|
2010-01-14 05:54:38 +00:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "" ["toc", "table-of-contents"]
|
|
|
|
(NoArg
|
|
|
|
(\opt -> return opt { optTableOfContents = True }))
|
|
|
|
"" -- "Include table of contents"
|
2014-02-25 22:43:58 -08:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "" ["toc-depth"]
|
|
|
|
(ReqArg
|
|
|
|
(\arg opt ->
|
|
|
|
case safeRead arg of
|
|
|
|
Just t | t >= 1 && t <= 6 ->
|
|
|
|
return opt { optTOCDepth = t }
|
|
|
|
_ -> err 57
|
|
|
|
"TOC level must be a number between 1 and 6")
|
|
|
|
"NUMBER")
|
|
|
|
"" -- "Number of levels to include in TOC"
|
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 08:11:08 +00:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "" ["no-highlight"]
|
|
|
|
(NoArg
|
2017-01-22 11:36:30 +01:00
|
|
|
(\opt -> return opt { optHighlightStyle = Nothing }))
|
2016-12-10 12:36:09 +01:00
|
|
|
"" -- "Don't highlight source code"
|
2008-08-10 17:33:20 +00:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "" ["highlight-style"]
|
|
|
|
(ReqArg
|
2017-02-04 22:44:09 +01:00
|
|
|
(\arg opt -> return opt{ optHighlightStyle = Just arg })
|
2016-12-10 12:36:09 +01:00
|
|
|
"STYLE")
|
|
|
|
"" -- "Style for highlighted code"
|
2014-12-26 11:19:55 -07:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "H" ["include-in-header"]
|
|
|
|
(ReqArg
|
2017-02-05 10:41:52 +01:00
|
|
|
(\arg opt -> return opt{ optIncludeInHeader =
|
|
|
|
arg : optIncludeInHeader opt,
|
|
|
|
optStandalone = True })
|
2016-12-10 12:36:09 +01:00
|
|
|
"FILENAME")
|
|
|
|
"" -- "File to include at end of header (implies -s)"
|
2016-12-03 17:17:30 +01:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "B" ["include-before-body"]
|
|
|
|
(ReqArg
|
2017-02-05 10:41:52 +01:00
|
|
|
(\arg opt -> return opt{ optIncludeBeforeBody =
|
|
|
|
arg : optIncludeBeforeBody opt,
|
|
|
|
optStandalone = True })
|
2016-12-10 12:36:09 +01:00
|
|
|
"FILENAME")
|
|
|
|
"" -- "File to include before document body"
|
2016-12-04 09:43:32 +01:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "A" ["include-after-body"]
|
|
|
|
(ReqArg
|
2017-02-05 10:41:52 +01:00
|
|
|
(\arg opt -> return opt{ optIncludeAfterBody =
|
|
|
|
arg : optIncludeAfterBody opt,
|
|
|
|
optStandalone = True })
|
2016-12-10 12:36:09 +01:00
|
|
|
"FILENAME")
|
|
|
|
"" -- "File to include after document body"
|
2015-08-13 15:24:50 -07:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "" ["self-contained"]
|
2016-10-23 21:18:22 +02:00
|
|
|
(NoArg
|
2016-12-10 12:36:09 +01:00
|
|
|
(\opt -> return opt { optSelfContained = True,
|
|
|
|
optStandalone = True }))
|
|
|
|
"" -- "Make slide shows include all the needed js and css"
|
2016-10-23 21:18:22 +02:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "" ["html-q-tags"]
|
2016-10-23 21:18:22 +02:00
|
|
|
(NoArg
|
2016-12-10 12:36:09 +01:00
|
|
|
(\opt ->
|
|
|
|
return opt { optHtmlQTags = True }))
|
|
|
|
"" -- "Use <q> tags for quotes in HTML"
|
2016-10-23 21:18:22 +02:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "" ["ascii"]
|
2016-10-23 21:18:22 +02:00
|
|
|
(NoArg
|
2016-12-10 12:36:09 +01:00
|
|
|
(\opt -> return opt { optAscii = True }))
|
|
|
|
"" -- "Use ascii characters only in HTML output"
|
2016-10-23 21:18:22 +02:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "" ["reference-links"]
|
2016-10-23 21:18:22 +02:00
|
|
|
(NoArg
|
2016-12-10 12:36:09 +01:00
|
|
|
(\opt -> return opt { optReferenceLinks = True } ))
|
|
|
|
"" -- "Use reference links in parsing HTML"
|
2016-10-23 21:18:22 +02:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "" ["reference-location"]
|
|
|
|
(ReqArg
|
|
|
|
(\arg opt -> do
|
|
|
|
action <- case arg of
|
|
|
|
"block" -> return EndOfBlock
|
|
|
|
"section" -> return EndOfSection
|
|
|
|
"document" -> return EndOfDocument
|
|
|
|
_ -> err 6
|
|
|
|
("Unknown option for reference-location: " ++ arg)
|
|
|
|
return opt { optReferenceLocation = action })
|
|
|
|
"block|section|document")
|
|
|
|
"" -- "Accepting or reject MS Word track-changes.""
|
|
|
|
|
|
|
|
, Option "" ["atx-headers"]
|
2016-10-23 21:18:22 +02:00
|
|
|
(NoArg
|
2016-12-10 12:36:09 +01:00
|
|
|
(\opt -> return opt { optSetextHeaders = False } ))
|
|
|
|
"" -- "Use atx-style headers for markdown"
|
2016-10-23 21:18:22 +02:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "" ["top-level-division"]
|
|
|
|
(ReqArg
|
|
|
|
(\arg opt -> do
|
|
|
|
let tldName = "TopLevel" ++ uppercaseFirstLetter arg
|
|
|
|
case safeRead tldName of
|
|
|
|
Just tlDiv -> return opt { optTopLevelDivision = tlDiv }
|
|
|
|
_ -> err 76 ("Top-level division must be " ++
|
|
|
|
"section, chapter, part, or default"))
|
|
|
|
"section|chapter|part")
|
|
|
|
"" -- "Use top-level division type in LaTeX, ConTeXt, DocBook"
|
|
|
|
|
|
|
|
, Option "N" ["number-sections"]
|
2006-12-22 20:16:03 +00:00
|
|
|
(NoArg
|
2016-12-10 12:36:09 +01:00
|
|
|
(\opt -> return opt { optNumberSections = True }))
|
|
|
|
"" -- "Number sections in LaTeX"
|
2006-12-22 20:16:03 +00:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "" ["number-offset"]
|
|
|
|
(ReqArg
|
|
|
|
(\arg opt ->
|
|
|
|
case safeRead ('[':arg ++ "]") of
|
|
|
|
Just ns -> return opt { optNumberOffset = ns,
|
|
|
|
optNumberSections = True }
|
|
|
|
_ -> err 57 "could not parse number-offset")
|
|
|
|
"NUMBERS")
|
|
|
|
"" -- "Starting number for sections, subsections, etc."
|
|
|
|
|
|
|
|
, Option "" ["listings"]
|
|
|
|
(NoArg
|
|
|
|
(\opt -> return opt { optListings = True }))
|
|
|
|
"" -- "Use listings package for LaTeX code blocks"
|
2006-12-22 20:16:03 +00:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "i" ["incremental"]
|
|
|
|
(NoArg
|
|
|
|
(\opt -> return opt { optIncremental = True }))
|
|
|
|
"" -- "Make list items display incrementally in Slidy/Slideous/S5"
|
2014-09-25 18:23:28 +01:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "" ["slide-level"]
|
|
|
|
(ReqArg
|
|
|
|
(\arg opt ->
|
|
|
|
case safeRead arg of
|
|
|
|
Just 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"
|
2013-09-17 21:04:27 -07:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "" ["section-divs"]
|
|
|
|
(NoArg
|
|
|
|
(\opt -> return opt { optSectionDivs = True }))
|
|
|
|
"" -- "Put sections in div tags in HTML"
|
2013-09-19 20:21:35 -07:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "" ["default-image-extension"]
|
|
|
|
(ReqArg
|
|
|
|
(\arg opt -> return opt { optDefaultImageExtension = arg })
|
|
|
|
"extension")
|
|
|
|
"" -- "Default extension for extensionless images"
|
2008-08-10 17:33:20 +00:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "" ["email-obfuscation"]
|
|
|
|
(ReqArg
|
|
|
|
(\arg opt -> do
|
|
|
|
method <- case arg of
|
|
|
|
"references" -> return ReferenceObfuscation
|
|
|
|
"javascript" -> return JavascriptObfuscation
|
|
|
|
"none" -> return NoObfuscation
|
|
|
|
_ -> err 6
|
|
|
|
("Unknown obfuscation method: " ++ arg)
|
|
|
|
return opt { optEmailObfuscation = method })
|
|
|
|
"none|javascript|references")
|
|
|
|
"" -- "Method for obfuscating email in HTML"
|
2006-12-28 02:20:09 +00:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "" ["id-prefix"]
|
|
|
|
(ReqArg
|
|
|
|
(\arg opt -> return opt { optIdentifierPrefix = arg })
|
|
|
|
"STRING")
|
|
|
|
"" -- "Prefix to add to automatically generated HTML identifiers"
|
2008-12-02 22:41:51 +00:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "T" ["title-prefix"]
|
|
|
|
(ReqArg
|
|
|
|
(\arg opt -> do
|
|
|
|
let newvars = ("title-prefix", arg) : optVariables opt
|
|
|
|
return opt { optVariables = newvars,
|
|
|
|
optStandalone = True })
|
|
|
|
"STRING")
|
|
|
|
"" -- "String to prefix to HTML window title"
|
2006-12-22 20:16:03 +00:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "c" ["css"]
|
|
|
|
(ReqArg
|
2017-02-05 10:41:52 +01:00
|
|
|
(\arg opt -> return opt{ optCss = arg : optCss opt })
|
|
|
|
-- add new link to end, so it is included in proper order
|
2016-12-10 12:36:09 +01:00
|
|
|
"URL")
|
|
|
|
"" -- "Link to CSS style sheet"
|
2014-07-31 16:26:48 -07:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "" ["reference-doc"]
|
|
|
|
(ReqArg
|
|
|
|
(\arg opt ->
|
|
|
|
return opt { optReferenceDoc = Just arg })
|
|
|
|
"FILENAME")
|
|
|
|
"" -- "Path of custom reference doc"
|
2014-07-31 16:26:48 -07:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "" ["epub-stylesheet"]
|
|
|
|
(ReqArg
|
2017-02-04 22:56:23 +01:00
|
|
|
(\arg opt -> return opt { optEpubStylesheet = Just arg })
|
2016-12-10 12:36:09 +01:00
|
|
|
"FILENAME")
|
|
|
|
"" -- "Path of epub.css"
|
2014-07-31 16:26:48 -07:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "" ["epub-cover-image"]
|
|
|
|
(ReqArg
|
|
|
|
(\arg opt ->
|
|
|
|
return opt { optVariables =
|
|
|
|
("epub-cover-image", arg) : optVariables opt })
|
|
|
|
"FILENAME")
|
|
|
|
"" -- "Path of epub cover image"
|
2014-07-31 16:26:48 -07:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "" ["epub-metadata"]
|
|
|
|
(ReqArg
|
2017-02-04 22:56:23 +01:00
|
|
|
(\arg opt -> return opt { optEpubMetadata = Just arg })
|
2016-12-10 12:36:09 +01:00
|
|
|
"FILENAME")
|
|
|
|
"" -- "Path of epub metadata file"
|
2014-07-31 16:26:48 -07:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "" ["epub-embed-font"]
|
|
|
|
(ReqArg
|
|
|
|
(\arg opt ->
|
|
|
|
return opt{ optEpubFonts = arg : optEpubFonts opt })
|
|
|
|
"FILE")
|
|
|
|
"" -- "Directory of fonts to embed"
|
2016-09-27 10:00:04 -04:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "" ["epub-chapter-level"]
|
|
|
|
(ReqArg
|
|
|
|
(\arg opt ->
|
|
|
|
case safeRead arg of
|
|
|
|
Just t | t >= 1 && t <= 6 ->
|
|
|
|
return opt { optEpubChapterLevel = t }
|
|
|
|
_ -> err 59
|
|
|
|
"chapter level must be a number between 1 and 6")
|
|
|
|
"NUMBER")
|
|
|
|
"" -- "Header level at which to split chapters in EPUB"
|
2014-07-31 16:26:48 -07:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "" ["latex-engine"]
|
|
|
|
(ReqArg
|
|
|
|
(\arg opt -> do
|
|
|
|
let b = takeBaseName arg
|
|
|
|
if b `elem` ["pdflatex", "lualatex", "xelatex"]
|
|
|
|
then return opt { optLaTeXEngine = arg }
|
|
|
|
else err 45 "latex-engine must be pdflatex, lualatex, or xelatex.")
|
|
|
|
"PROGRAM")
|
|
|
|
"" -- "Name of latex program to use in generating PDF"
|
2015-12-11 15:58:11 -08:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "" ["latex-engine-opt"]
|
|
|
|
(ReqArg
|
|
|
|
(\arg opt -> do
|
|
|
|
let oldArgs = optLaTeXEngineArgs opt
|
|
|
|
return opt { optLaTeXEngineArgs = arg : oldArgs })
|
|
|
|
"STRING")
|
|
|
|
"" -- "Flags to pass to the LaTeX engine, all instances of this option are accumulated and used"
|
2006-12-22 20:16:03 +00:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "" ["bibliography"]
|
|
|
|
(ReqArg
|
2017-02-05 21:58:45 +01:00
|
|
|
(\arg opt -> return opt{ optMetadata =
|
|
|
|
("bibliography", arg) : optMetadata opt })
|
2016-12-10 12:36:09 +01:00
|
|
|
"FILE")
|
|
|
|
""
|
2007-01-02 07:37:42 +00:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "" ["csl"]
|
|
|
|
(ReqArg
|
|
|
|
(\arg opt ->
|
2017-02-05 21:58:45 +01:00
|
|
|
return opt{ optMetadata =
|
|
|
|
("csl", arg) : optMetadata opt })
|
2016-12-10 12:36:09 +01:00
|
|
|
"FILE")
|
|
|
|
""
|
2006-12-22 20:16:03 +00:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "" ["citation-abbreviations"]
|
|
|
|
(ReqArg
|
|
|
|
(\arg opt ->
|
2017-02-05 21:58:45 +01:00
|
|
|
return opt{ optMetadata =
|
|
|
|
("citation-abbreviations", arg): optMetadata opt })
|
2016-12-10 12:36:09 +01:00
|
|
|
"FILE")
|
|
|
|
""
|
2006-10-17 14:22:29 +00:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "" ["natbib"]
|
|
|
|
(NoArg
|
|
|
|
(\opt -> return opt { optCiteMethod = Natbib }))
|
|
|
|
"" -- "Use natbib cite commands in LaTeX output"
|
2006-10-17 14:22:29 +00:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "" ["biblatex"]
|
|
|
|
(NoArg
|
|
|
|
(\opt -> return opt { optCiteMethod = Biblatex }))
|
|
|
|
"" -- "Use biblatex cite commands in LaTeX output"
|
2006-10-17 14:22:29 +00:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "m" ["latexmathml", "asciimathml"]
|
|
|
|
(OptArg
|
|
|
|
(\arg opt ->
|
|
|
|
return opt { optHTMLMathMethod = LaTeXMathML arg })
|
|
|
|
"URL")
|
|
|
|
"" -- "Use LaTeXMathML script in html output"
|
2007-01-09 01:43:23 +00:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "" ["mathml"]
|
2017-01-30 11:31:50 +01:00
|
|
|
(NoArg
|
|
|
|
(\opt ->
|
|
|
|
return opt { optHTMLMathMethod = MathML }))
|
2016-12-10 12:36:09 +01:00
|
|
|
"" -- "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' = fromMaybe "https://latex.codecogs.com/png.latex?" arg
|
|
|
|
return opt { optHTMLMathMethod = WebTeX url' })
|
|
|
|
"URL")
|
|
|
|
"" -- "Use web service for HTML math"
|
2014-09-25 18:23:28 +01:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "" ["jsmath"]
|
|
|
|
(OptArg
|
|
|
|
(\arg opt -> return opt { optHTMLMathMethod = JsMath arg})
|
|
|
|
"URL")
|
|
|
|
"" -- "Use jsMath for HTML math"
|
2014-09-25 18:23:28 +01:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "" ["mathjax"]
|
|
|
|
(OptArg
|
|
|
|
(\arg opt -> do
|
|
|
|
let url' = fromMaybe "https://cdn.mathjax.org/mathjax/latest/MathJax.js?config=TeX-AMS_CHTML-full" arg
|
|
|
|
return opt { optHTMLMathMethod = MathJax url'})
|
|
|
|
"URL")
|
|
|
|
"" -- "Use MathJax for HTML math"
|
|
|
|
, Option "" ["katex"]
|
|
|
|
(OptArg
|
|
|
|
(\arg opt ->
|
|
|
|
return opt
|
|
|
|
{ optKaTeXJS =
|
|
|
|
arg <|> Just "https://cdnjs.cloudflare.com/ajax/libs/KaTeX/0.6.0/katex.min.js"})
|
|
|
|
"URL")
|
|
|
|
"" -- Use KaTeX for HTML Math
|
2013-09-10 20:23:03 -07:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "" ["katex-stylesheet"]
|
|
|
|
(ReqArg
|
|
|
|
(\arg opt ->
|
|
|
|
return opt { optKaTeXStylesheet = Just arg })
|
|
|
|
"URL")
|
|
|
|
"" -- Set the KaTeX Stylesheet location
|
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 08:11:08 +00:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "" ["gladtex"]
|
|
|
|
(NoArg
|
|
|
|
(\opt -> return opt { optHTMLMathMethod = GladTeX }))
|
|
|
|
"" -- "Use gladtex for HTML math"
|
2010-01-14 05:54:38 +00:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "" ["trace"]
|
|
|
|
(NoArg
|
2017-01-22 12:19:46 +01:00
|
|
|
(\opt -> return opt { optVerbosity = DEBUG }))
|
2016-12-10 12:36:09 +01:00
|
|
|
"" -- "Turn on diagnostic tracing in readers."
|
2014-04-27 20:38:15 -07:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "" ["dump-args"]
|
|
|
|
(NoArg
|
|
|
|
(\opt -> return opt { optDumpArgs = True }))
|
|
|
|
"" -- "Print output filename and arguments to stdout."
|
2006-12-28 02:20:09 +00:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "" ["ignore-args"]
|
|
|
|
(NoArg
|
|
|
|
(\opt -> return opt { optIgnoreArgs = True }))
|
|
|
|
"" -- "Ignore command-line arguments."
|
2012-01-28 11:41:26 -08:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "" ["verbose"]
|
|
|
|
(NoArg
|
2017-01-22 12:19:46 +01:00
|
|
|
(\opt -> return opt { optVerbosity = INFO }))
|
2016-12-10 12:36:09 +01:00
|
|
|
"" -- "Verbose diagnostic output."
|
2012-03-09 10:32:32 -08:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "" ["quiet"]
|
|
|
|
(NoArg
|
2017-01-22 12:19:46 +01:00
|
|
|
(\opt -> return opt { optVerbosity = ERROR }))
|
2016-12-10 12:36:09 +01:00
|
|
|
"" -- "Suppress warnings."
|
2015-11-19 20:18:06 -08:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "" ["fail-if-warnings"]
|
|
|
|
(NoArg
|
|
|
|
(\opt -> return opt { optFailIfWarnings = True }))
|
|
|
|
"" -- "Exit with error status if there were warnings."
|
2016-11-27 15:45:08 +01:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "" ["bash-completion"]
|
|
|
|
(NoArg
|
|
|
|
(\_ -> do
|
|
|
|
ddir <- getDataDir
|
|
|
|
tpl <- readDataFileUTF8 Nothing "bash_completion.tpl"
|
|
|
|
let optnames (Option shorts longs _ _) =
|
|
|
|
map (\c -> ['-',c]) shorts ++
|
|
|
|
map ("--" ++) longs
|
|
|
|
let allopts = unwords (concatMap optnames options)
|
|
|
|
UTF8.hPutStrLn stdout $ printf tpl allopts
|
2017-02-05 21:58:45 +01:00
|
|
|
(unwords readers'names)
|
|
|
|
(unwords writers'names)
|
2016-12-10 12:36:09 +01:00
|
|
|
(unwords $ map fst highlightingStyles)
|
|
|
|
ddir
|
|
|
|
exitSuccess ))
|
|
|
|
"" -- "Print bash completion script"
|
2012-01-21 09:34:47 -08:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "" ["list-input-formats"]
|
|
|
|
(NoArg
|
|
|
|
(\_ -> do
|
|
|
|
mapM_ (UTF8.hPutStrLn stdout) readers'names
|
|
|
|
exitSuccess ))
|
|
|
|
""
|
2006-12-28 02:20:09 +00:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "" ["list-output-formats"]
|
|
|
|
(NoArg
|
|
|
|
(\_ -> do
|
|
|
|
mapM_ (UTF8.hPutStrLn stdout) writers'names
|
|
|
|
exitSuccess ))
|
|
|
|
""
|
2011-11-22 14:21:19 -08:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "" ["list-extensions"]
|
|
|
|
(NoArg
|
|
|
|
(\_ -> do
|
|
|
|
let showExt x = drop 4 (show x) ++
|
2017-01-14 13:06:27 +01:00
|
|
|
if extensionEnabled x pandocExtensions
|
2016-12-10 12:36:09 +01:00
|
|
|
then " +"
|
|
|
|
else " -"
|
|
|
|
mapM_ (UTF8.hPutStrLn stdout . showExt)
|
|
|
|
([minBound..maxBound] :: [Extension])
|
|
|
|
exitSuccess ))
|
|
|
|
""
|
2006-12-22 20:16:03 +00:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "" ["list-highlight-languages"]
|
|
|
|
(NoArg
|
|
|
|
(\_ -> do
|
|
|
|
let langs = [ T.unpack (T.toLower (sShortname s))
|
|
|
|
| s <- M.elems defaultSyntaxMap
|
|
|
|
, sShortname s `notElem`
|
|
|
|
[T.pack "Alert", T.pack "Alert_indent"]
|
|
|
|
]
|
|
|
|
mapM_ (UTF8.hPutStrLn stdout) langs
|
|
|
|
exitSuccess ))
|
|
|
|
""
|
2009-12-31 01:13:16 +00:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "" ["list-highlight-styles"]
|
|
|
|
(NoArg
|
|
|
|
(\_ -> do
|
|
|
|
mapM_ (UTF8.hPutStrLn stdout) $
|
|
|
|
map fst highlightingStyles
|
|
|
|
exitSuccess ))
|
|
|
|
""
|
2014-08-02 16:07:19 -07:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "v" ["version"]
|
|
|
|
(NoArg
|
|
|
|
(\_ -> do
|
|
|
|
prg <- getProgName
|
|
|
|
defaultDatadir <- E.catch
|
|
|
|
(getAppUserDataDirectory "pandoc")
|
|
|
|
(\e -> let _ = (e :: E.SomeException)
|
|
|
|
in return "")
|
|
|
|
UTF8.hPutStrLn stdout (prg ++ " " ++ pandocVersion ++
|
|
|
|
compileInfo ++ "\nDefault user data directory: " ++
|
|
|
|
defaultDatadir ++ copyrightMessage)
|
|
|
|
exitSuccess ))
|
|
|
|
"" -- "Print version"
|
2010-07-08 17:14:03 -07:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
, Option "h" ["help"]
|
|
|
|
(NoArg
|
|
|
|
(\_ -> do
|
|
|
|
prg <- getProgName
|
|
|
|
UTF8.hPutStr stdout (usageMessage prg options)
|
|
|
|
exitSuccess ))
|
|
|
|
"" -- "Show help"
|
|
|
|
|
|
|
|
]
|
2010-07-08 17:14:03 -07:00
|
|
|
|
2016-12-10 12:36:09 +01:00
|
|
|
-- Returns usage message
|
|
|
|
usageMessage :: String -> [OptDescr (Opt -> IO Opt)] -> String
|
|
|
|
usageMessage programName = usageInfo (programName ++ " [OPTIONS] [FILES]")
|
2016-12-10 11:12:23 +01:00
|
|
|
|
2017-02-05 21:58:45 +01:00
|
|
|
copyrightMessage :: String
|
|
|
|
copyrightMessage = intercalate "\n" [
|
|
|
|
"",
|
|
|
|
"Copyright (C) 2006-2016 John MacFarlane",
|
|
|
|
"Web: http://pandoc.org",
|
|
|
|
"This is free software; see the source for copying conditions.",
|
|
|
|
"There is no warranty, not even for merchantability or fitness",
|
|
|
|
"for a particular purpose." ]
|
|
|
|
|
|
|
|
compileInfo :: String
|
|
|
|
compileInfo =
|
|
|
|
"\nCompiled with pandoc-types " ++ VERSION_pandoc_types ++ ", texmath " ++
|
|
|
|
VERSION_texmath ++ ", skylighting " ++ VERSION_skylighting
|
|
|
|
|
|
|
|
-- | Converts a list of strings into a single string with the items printed as
|
|
|
|
-- comma separated words in lines with a maximum line length.
|
|
|
|
wrapWords :: Int -> Int -> [String] -> String
|
|
|
|
wrapWords indent c = wrap' (c - indent) (c - indent)
|
|
|
|
where
|
|
|
|
wrap' _ _ [] = ""
|
|
|
|
wrap' cols remaining (x:xs)
|
|
|
|
| remaining == cols =
|
|
|
|
x ++ wrap' cols (remaining - length x) xs
|
|
|
|
| (length x + 1) > remaining =
|
|
|
|
",\n" ++ replicate indent ' ' ++ x ++
|
|
|
|
wrap' cols (cols - length x) xs
|
|
|
|
| otherwise =
|
|
|
|
", " ++ x ++
|
|
|
|
wrap' cols (remaining - length x - 2) xs
|
|
|
|
|
|
|
|
addDeprecationNote :: String -> [String] -> [String]
|
|
|
|
addDeprecationNote "--smart" =
|
|
|
|
(("--smart has been removed. Use +smart or -smart extension instead.\n" ++
|
|
|
|
"For example: pandoc -f markdown+smart -t markdown-smart.") :)
|
|
|
|
addDeprecationNote "-S" = addDeprecationNote "--smart"
|
|
|
|
addDeprecationNote "--old-dashes" =
|
|
|
|
("--old-dashes has been removed. Use +old_dashes extension instead." :)
|
|
|
|
addDeprecationNote "--no-wrap" =
|
|
|
|
("--no-wrap has been removed. Use --wrap=none instead." :)
|
|
|
|
addDeprecationNote "--chapters" =
|
|
|
|
("--chapters has been removed. Use --top-level-division=chapter instead." :)
|
|
|
|
addDeprecationNote "--reference-docx" =
|
|
|
|
("--reference-docx has been removed. Use --reference-doc instead." :)
|
|
|
|
addDeprecationNote "--reference-odt" =
|
|
|
|
("--reference-odt has been removed. Use --reference-doc instead." :)
|
|
|
|
addDeprecationNote x =
|
|
|
|
(("Unknown option " ++ x ++ ".") :)
|
2016-12-10 12:36:09 +01:00
|
|
|
|
|
|
|
uppercaseFirstLetter :: String -> String
|
|
|
|
uppercaseFirstLetter (c:cs) = toUpper c : cs
|
|
|
|
uppercaseFirstLetter [] = []
|
2016-12-10 12:11:25 +01:00
|
|
|
|
2017-02-05 21:58:45 +01:00
|
|
|
readers'names :: [String]
|
|
|
|
readers'names = sort (map fst (readers :: [(String, Reader PandocIO)]))
|
|
|
|
|
|
|
|
writers'names :: [String]
|
|
|
|
writers'names = sort (map fst (writers :: [(String, Writer PandocIO)]))
|
|
|
|
|
|
|
|
splitField :: String -> (String, String)
|
|
|
|
splitField s =
|
|
|
|
case break (`elem` ":=") s of
|
|
|
|
(k,_:v) -> (k,v)
|
|
|
|
(k,[]) -> (k,"true")
|