aboutsummaryrefslogtreecommitdiff
path: root/pandoc.hs
diff options
context:
space:
mode:
Diffstat (limited to 'pandoc.hs')
-rw-r--r--pandoc.hs48
1 files changed, 32 insertions, 16 deletions
diff --git a/pandoc.hs b/pandoc.hs
index 2290f750a..9495599f0 100644
--- a/pandoc.hs
+++ b/pandoc.hs
@@ -49,7 +49,7 @@ import System.Exit ( exitWith, ExitCode (..) )
import System.FilePath
import System.Console.GetOpt
import Data.Char ( toLower )
-import Data.List ( intercalate, isPrefixOf, isSuffixOf, sort )
+import Data.List ( delete, intercalate, isPrefixOf, isSuffixOf, sort )
import System.Directory ( getAppUserDataDirectory, findExecutable,
doesFileExist, Permissions(..), getPermissions )
import System.IO ( stdout, stderr )
@@ -72,6 +72,8 @@ import Control.Applicative ((<$>), (<|>))
import Text.Pandoc.Readers.Txt2Tags (getT2TMeta)
import Data.Monoid
+import Text.Pandoc.Error
+
type Transform = Pandoc -> Pandoc
copyrightMessage :: String
@@ -198,6 +200,7 @@ data Opt = Opt
, optCiteMethod :: CiteMethod -- ^ Method to output cites
, optListings :: Bool -- ^ Use listings package for code blocks
, optLaTeXEngine :: String -- ^ Program to use for latex -> pdf
+ , optLaTeXEngineArgs :: [String] -- ^ Flags to pass to the latex-engine
, optSlideLevel :: Maybe Int -- ^ Header level that creates slides
, optSetextHeaders :: Bool -- ^ Use atx headers for markdown level 1-2
, optAscii :: Bool -- ^ Use ascii characters only in html
@@ -259,6 +262,7 @@ defaultOpts = Opt
, optCiteMethod = Citeproc
, optListings = False
, optLaTeXEngine = "pdflatex"
+ , optLaTeXEngineArgs = []
, optSlideLevel = Nothing
, optSetextHeaders = True
, optAscii = False
@@ -734,6 +738,14 @@ options =
"PROGRAM")
"" -- "Name of latex program to use in generating PDF"
+ , 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"
+
, Option "" ["bibliography"]
(ReqArg
(\arg opt -> return opt{ optMetadata = addMetadata
@@ -905,13 +917,15 @@ readMetaValue s = case decode (UTF8.fromString s) of
usageMessage :: String -> [OptDescr (Opt -> IO Opt)] -> String
usageMessage programName = usageInfo
(programName ++ " [OPTIONS] [FILES]" ++ "\nInput formats: " ++
- (wrapWords 16 78 $ readers'names) ++ "\nOutput formats: " ++
+ (wrapWords 16 78 $ readers'names) ++
+ '\n' : replicate 16 ' ' ++
+ "[ *only Pandoc's JSON version of native AST]" ++ "\nOutput formats: " ++
(wrapWords 16 78 $ writers'names) ++
'\n' : replicate 16 ' ' ++
- "[*for pdf output, use latex or beamer and -o FILENAME.pdf]\nOptions:")
+ "[**for pdf output, use latex or beamer and -o FILENAME.pdf]\nOptions:")
where
- writers'names = sort $ "pdf*" : map fst writers
- readers'names = sort $ map fst readers
+ writers'names = sort $ "json*" : "pdf**" : delete "json" (map fst writers)
+ readers'names = sort $ "json*" : delete "json" (map fst readers)
-- Determine default reader based on source file extensions
defaultReaderName :: String -> [FilePath] -> String
@@ -1080,6 +1094,7 @@ main = do
, optCiteMethod = citeMethod
, optListings = listings
, optLaTeXEngine = latexEngine
+ , optLaTeXEngineArgs = latexEngineArgs
, optSlideLevel = slideLevel
, optSetextHeaders = setextHeaders
, optAscii = ascii
@@ -1262,17 +1277,17 @@ main = do
then 0
else tabStop)
- let handleIncludes' = if readerName' == "latex" ||
- readerName' == "latex+lhs"
+ let handleIncludes' :: String -> IO (Either PandocError String)
+ handleIncludes' = if readerName' `elem` ["latex", "latex+lhs"]
then handleIncludes
- else return
-
- (doc, media) <-
- case reader of
- StringReader r-> (, mempty) <$>
- ( readSources >=>
- handleIncludes' . convertTabs . intercalate "\n" >=>
- r readerOpts ) sources
+ else return . Right
+
+ (doc, media) <- fmap handleError $
+ case reader of
+ StringReader r-> do
+ srcs <- convertTabs . intercalate "\n" <$> readSources sources
+ doc <- handleIncludes' srcs
+ either (return . Left) (\s -> fmap (,mempty) <$> r readerOpts s) doc
ByteStringReader r -> readFiles sources >>= r readerOpts
let writerOptions = def { writerStandalone = standalone',
@@ -1312,7 +1327,8 @@ main = do
writerReferenceODT = referenceODT,
writerReferenceDocx = referenceDocx,
writerMediaBag = media,
- writerVerbose = verbose
+ writerVerbose = verbose,
+ writerLaTeXArgs = latexEngineArgs
}