aboutsummaryrefslogtreecommitdiff
path: root/pandoc.hs
diff options
context:
space:
mode:
Diffstat (limited to 'pandoc.hs')
-rw-r--r--pandoc.hs38
1 files changed, 27 insertions, 11 deletions
diff --git a/pandoc.hs b/pandoc.hs
index 8c196c01d..709b5a777 100644
--- a/pandoc.hs
+++ b/pandoc.hs
@@ -35,7 +35,8 @@ import Text.Pandoc.Builder (setMeta)
import Text.Pandoc.PDF (makePDF)
import Text.Pandoc.Readers.LaTeX (handleIncludes)
import Text.Pandoc.Shared ( tabFilter, readDataFileUTF8, readDataFile,
- safeRead, headerShift, normalize, err, warn )
+ safeRead, headerShift, normalize, err, warn,
+ openURL )
import Text.Pandoc.XML ( toEntities )
import Text.Pandoc.SelfContained ( makeSelfContained )
import Text.Pandoc.Process (pipeProcess)
@@ -55,7 +56,6 @@ import Control.Exception.Extensible ( throwIO )
import qualified Text.Pandoc.UTF8 as UTF8
import Control.Monad (when, unless, liftM)
import Data.Foldable (foldrM)
-import Network.HTTP (simpleHTTP, mkRequest, getResponseBody, RequestMethod(..))
import Network.URI (parseURI, isURI, URI(..))
import qualified Data.ByteString.Lazy as B
import qualified Data.ByteString as BS
@@ -162,6 +162,7 @@ data Opt = Opt
, optAscii :: Bool -- ^ Use ascii characters only in html
, optTeXLigatures :: Bool -- ^ Use TeX ligatures for quotes/dashes
, optDefaultImageExtension :: String -- ^ Default image extension
+ , optTrace :: Bool -- ^ Print debug information
}
-- | Defaults for command-line options.
@@ -217,6 +218,7 @@ defaultOpts = Opt
, optAscii = False
, optTeXLigatures = True
, optDefaultImageExtension = ""
+ , optTrace = False
}
-- | A list of functions, each transforming the options data structure
@@ -656,7 +658,7 @@ options =
(ReqArg
(\arg opt -> do
let b = takeBaseName arg
- if (b == "pdflatex" || b == "lualatex" || b == "xelatex")
+ if b `elem` ["pdflatex", "lualatex", "xelatex"]
then return opt { optLaTeXEngine = arg }
else err 45 "latex-engine must be pdflatex, lualatex, or xelatex.")
"PROGRAM")
@@ -667,6 +669,9 @@ options =
(\arg opt -> return opt{ optMetadata = addMetadata
"bibliography" (readMetaValue arg)
$ optMetadata opt
+ , optVariables =
+ ("biblio-files", dropExtension arg) :
+ optVariables opt
})
"FILE")
""
@@ -755,6 +760,11 @@ options =
(\opt -> return opt { optHTMLMathMethod = GladTeX }))
"" -- "Use gladtex for HTML math"
+ , Option "" ["trace"]
+ (NoArg
+ (\opt -> return opt { optTrace = True }))
+ "" -- "Turn on diagnostic tracing in readers."
+
, Option "" ["dump-args"]
(NoArg
(\opt -> return opt { optDumpArgs = True }))
@@ -824,6 +834,7 @@ defaultReaderName fallback (x:xs) =
".latex" -> "latex"
".ltx" -> "latex"
".rst" -> "rst"
+ ".org" -> "org"
".lhs" -> "markdown+lhs"
".db" -> "docbook"
".opml" -> "opml"
@@ -949,6 +960,7 @@ main = do
, optAscii = ascii
, optTeXLigatures = texLigatures
, optDefaultImageExtension = defaultImageExtension
+ , optTrace = trace
} = opts
when dumpArgs $
@@ -958,7 +970,9 @@ main = do
-- --bibliography implies -F pandoc-citeproc for backwards compatibility:
let filters' = case M.lookup "bibliography" metadata of
- Just _ | all (\f -> takeBaseName f /= "pandoc-citeproc")
+ Just _ | optCiteMethod opts /= Natbib &&
+ optCiteMethod opts /= Biblatex &&
+ all (\f -> takeBaseName f /= "pandoc-citeproc")
filters -> "pandoc-citeproc" : filters
_ -> filters
let plugins = map externalFilter filters'
@@ -1034,12 +1048,10 @@ main = do
variables' <- case mathMethod of
LaTeXMathML Nothing -> do
- s <- readDataFileUTF8 datadir
- ("LaTeXMathML.js")
+ s <- readDataFileUTF8 datadir "LaTeXMathML.js"
return $ ("mathml-script", s) : variables
MathML Nothing -> do
- s <- readDataFileUTF8 datadir
- ("MathMLinHTML.js")
+ s <- readDataFileUTF8 datadir "MathMLinHTML.js"
return $ ("mathml-script", s) : variables
_ -> return variables
@@ -1071,6 +1083,7 @@ main = do
, readerIndentedCodeClasses = codeBlockClasses
, readerApplyMacros = not laTeXOutput
, readerDefaultImageExtension = defaultImageExtension
+ , readerTrace = trace
}
let writerOptions = def { writerStandalone = standalone',
@@ -1120,10 +1133,13 @@ main = do
readSource "-" = UTF8.getContents
readSource src = case parseURI src of
Just u | uriScheme u `elem` ["http:","https:"] ->
- readURI u
+ readURI src
_ -> UTF8.readFile src
- readURI uri = simpleHTTP (mkRequest GET uri) >>= getResponseBody >>=
- return . UTF8.toStringLazy -- treat all as UTF8
+ readURI src = do
+ res <- openURL src
+ case res of
+ Left e -> throwIO e
+ Right (bs,_) -> return $ UTF8.toString bs
let convertTabs = tabFilter (if preserveTabs then 0 else tabStop)