aboutsummaryrefslogtreecommitdiff
path: root/pandoc.hs
diff options
context:
space:
mode:
Diffstat (limited to 'pandoc.hs')
-rw-r--r--pandoc.hs101
1 files changed, 70 insertions, 31 deletions
diff --git a/pandoc.hs b/pandoc.hs
index 71d0c4b98..fb9b9abbf 100644
--- a/pandoc.hs
+++ b/pandoc.hs
@@ -1,6 +1,6 @@
{-# LANGUAGE CPP, TupleSections #-}
{-
-Copyright (C) 2006-2014 John MacFarlane <jgm@berkeley.edu>
+Copyright (C) 2006-2015 John MacFarlane <jgm@berkeley.edu>
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
@@ -19,7 +19,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
{- |
Module : Main
- Copyright : Copyright (C) 2006-2014 John MacFarlane
+ Copyright : Copyright (C) 2006-2015 John MacFarlane
License : GNU GPL, version 2 or above
Maintainer : John MacFarlane <jgm@berkeley@edu>
@@ -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 )
@@ -58,7 +58,7 @@ import qualified Control.Exception as E
import Control.Exception.Extensible ( throwIO )
import qualified Text.Pandoc.UTF8 as UTF8
import Control.Monad (when, unless, (>=>))
-import Data.Maybe (isJust, fromMaybe)
+import Data.Maybe (fromMaybe, isNothing)
import Data.Foldable (foldrM)
import Network.URI (parseURI, isURI, URI(..))
import qualified Data.ByteString.Lazy as B
@@ -72,13 +72,15 @@ import Control.Applicative ((<$>), (<|>))
import Text.Pandoc.Readers.Txt2Tags (getT2TMeta)
import Data.Monoid
+import Text.Pandoc.Error
+
type Transform = Pandoc -> Pandoc
copyrightMessage :: String
copyrightMessage = intercalate "\n" [
"",
- "Copyright (C) 2006-2014 John MacFarlane",
- "Web: http://johnmacfarlane.net/pandoc",
+ "Copyright (C) 2006-2015 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." ]
@@ -140,12 +142,18 @@ externalFilter f args' d = do
".php" -> ("php", f:args')
_ -> (f, args')
else err 85 $ "Filter " ++ f ++ " not found"
+ when (f' /= f) $ do
+ mbExe <- findExecutable f'
+ when (isNothing mbExe) $
+ err 83 $ "Error running filter " ++ f ++ "\n" ++
+ show f' ++ " not found in path."
(exitcode, outbs, errbs) <- E.handle filterException $
pipeProcess Nothing f' args'' $ encode d
when (not $ B.null errbs) $ B.hPutStr stderr errbs
case exitcode of
ExitSuccess -> return $ either error id $ eitherDecode' outbs
- ExitFailure _ -> err 83 $ "Error running filter " ++ f
+ ExitFailure ec -> err 83 $ "Error running filter " ++ f ++ "\n" ++
+ "Filter returned error status " ++ show ec
where filterException :: E.SomeException -> IO a
filterException e = err 83 $ "Error running filter " ++ f ++ "\n" ++
show e
@@ -186,6 +194,7 @@ data Opt = Opt
, optTOCDepth :: Int -- ^ Number of levels to include in TOC
, optDumpArgs :: Bool -- ^ Output command-line arguments
, optIgnoreArgs :: Bool -- ^ Ignore command-line arguments
+ , optVerbose :: Bool -- ^ Verbose diagnostic output
, optReferenceLinks :: Bool -- ^ Use reference links in writing markdown, rst
, optWrapText :: Bool -- ^ Wrap text
, optColumns :: Int -- ^ Line length in characters
@@ -197,6 +206,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
@@ -246,6 +256,7 @@ defaultOpts = Opt
, optTOCDepth = 3
, optDumpArgs = False
, optIgnoreArgs = False
+ , optVerbose = False
, optReferenceLinks = False
, optWrapText = True
, optColumns = 72
@@ -257,6 +268,7 @@ defaultOpts = Opt
, optCiteMethod = Citeproc
, optListings = False
, optLaTeXEngine = "pdflatex"
+ , optLaTeXEngineArgs = []
, optSlideLevel = Nothing
, optSetextHeaders = True
, optAscii = False
@@ -732,14 +744,19 @@ 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
"bibliography" (readMetaValue arg)
$ optMetadata opt
- , optVariables =
- ("biblio-files", dropExtension arg) :
- optVariables opt
})
"FILE")
""
@@ -818,7 +835,7 @@ options =
(\arg opt -> do
let url' = case arg of
Just u -> u
- Nothing -> "//cdn.mathjax.org/mathjax/latest/MathJax.js?config=TeX-AMS-MML_HTMLorMML"
+ Nothing -> "https://cdn.mathjax.org/mathjax/latest/MathJax.js?config=TeX-AMS-MML_HTMLorMML"
return opt { optHTMLMathMethod = MathJax url'})
"URL")
"" -- "Use MathJax for HTML math"
@@ -827,7 +844,7 @@ options =
(\arg opt ->
return opt
{ optKaTeXJS =
- arg <|> Just "http://cdnjs.cloudflare.com/ajax/libs/KaTeX/0.1.0/katex.min.js"})
+ arg <|> Just "https://cdnjs.cloudflare.com/ajax/libs/KaTeX/0.1.0/katex.min.js"})
"URL")
"" -- Use KaTeX for HTML Math
@@ -858,6 +875,11 @@ options =
(\opt -> return opt { optIgnoreArgs = True }))
"" -- "Ignore command-line arguments."
+ , Option "" ["verbose"]
+ (NoArg
+ (\opt -> return opt { optVerbose = True }))
+ "" -- "Verbose diagnostic output."
+
, Option "v" ["version"]
(NoArg
(\_ -> do
@@ -898,13 +920,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
@@ -930,6 +954,9 @@ defaultReaderName fallback (x:xs) =
".docx" -> "docx"
".t2t" -> "t2t"
".epub" -> "epub"
+ ".odt" -> "odt"
+ ".pdf" -> "pdf" -- so we get an "unknown reader" error
+ ".doc" -> "doc" -- so we get an "unknown reader" error
_ -> defaultReaderName fallback xs
-- Returns True if extension of first source is .lhs
@@ -970,6 +997,7 @@ defaultWriterName x =
".pdf" -> "latex"
".fb2" -> "fb2"
".opml" -> "opml"
+ ".icml" -> "icml"
['.',y] | y `elem` ['1'..'9'] -> "man"
_ -> "html"
@@ -1057,6 +1085,7 @@ main = do
, optTOCDepth = epubTOCDepth
, optDumpArgs = dumpArgs
, optIgnoreArgs = ignoreArgs
+ , optVerbose = verbose
, optReferenceLinks = referenceLinks
, optWrapText = wrap
, optColumns = columns
@@ -1068,6 +1097,7 @@ main = do
, optCiteMethod = citeMethod
, optListings = listings
, optLaTeXEngine = latexEngine
+ , optLaTeXEngineArgs = latexEngineArgs
, optSlideLevel = slideLevel
, optSetextHeaders = setextHeaders
, optAscii = ascii
@@ -1085,7 +1115,7 @@ main = do
mapM_ (\arg -> UTF8.hPutStrLn stdout arg) args
exitWith ExitSuccess
- let csscdn = "http://cdnjs.cloudflare.com/ajax/libs/KaTeX/0.1.0/katex.min.css"
+ let csscdn = "https://cdnjs.cloudflare.com/ajax/libs/KaTeX/0.1.0/katex.min.css"
let mathMethod =
case (katexJS, katexStylesheet) of
(Nothing, _) -> mathMethod'
@@ -1093,7 +1123,7 @@ main = do
-- --bibliography implies -F pandoc-citeproc for backwards compatibility:
- let needsCiteproc = isJust (M.lookup "bibliography" metadata) &&
+ let needsCiteproc = any ("--bibliography" `isPrefixOf`) rawArgs &&
optCiteMethod opts `notElem` [Natbib, Biblatex] &&
"pandoc-citeproc" `notElem` map takeBaseName filters
let filters' = if needsCiteproc then "pandoc-citeproc" : filters
@@ -1148,7 +1178,13 @@ main = do
(getT2TMeta sources outputFile)
else case getReader readerName' of
Right r -> return r
- Left e -> err 7 e
+ Left e -> err 7 e'
+ where e' = case readerName' of
+ "pdf" -> e ++
+ "\nPandoc can convert to PDF, but not from PDF."
+ "doc" -> e ++
+ "\nPandoc can convert from DOCX, but not from DOC.\nTry using Word to save your DOC file as DOCX, and convert that with pandoc."
+ _ -> e
let standalone' = standalone || not (isTextFormat writerName') || pdfOutput
@@ -1235,23 +1271,24 @@ main = do
Right (bs,_) -> return $ UTF8.toString bs
let readFiles [] = error "Cannot read archive from stdin"
- readFiles (x:_) = B.readFile x
+ readFiles [x] = B.readFile x
+ readFiles (x:xs) = mapM (warn . ("Ignoring: " ++)) xs >> B.readFile x
let convertTabs = tabFilter (if preserveTabs || readerName' == "t2t"
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',
@@ -1290,7 +1327,9 @@ main = do
writerTOCDepth = epubTOCDepth,
writerReferenceODT = referenceODT,
writerReferenceDocx = referenceDocx,
- writerMediaBag = media
+ writerMediaBag = media,
+ writerVerbose = verbose,
+ writerLaTeXArgs = latexEngineArgs
}