diff options
Diffstat (limited to 'pandoc.hs')
-rw-r--r-- | pandoc.hs | 109 |
1 files changed, 73 insertions, 36 deletions
@@ -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,11 +56,16 @@ 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 import Data.Aeson (eitherDecode', encode) +import qualified Data.Map as M +import System.IO.Error(ioeGetErrorType) +import GHC.IO.Exception (IOErrorType(ResourceVanished)) +import Data.Yaml (decode) +import qualified Data.Yaml as Yaml +import qualified Data.Text as T copyrightMessage :: String copyrightMessage = "\nCopyright (C) 2006-2013 John MacFarlane\n" ++ @@ -98,8 +104,11 @@ externalFilter f args' d = do ExitSuccess -> return $ either error id $ eitherDecode' outbs ExitFailure _ -> err 83 $ "Error running filter " ++ f where filterException :: E.SomeException -> IO a - filterException e = err 83 $ "Error running filter " ++ f ++ - "\n" ++ show e + filterException e = err 83 $ "Error running filter " ++ f ++ "\n" ++ + if ioeGetErrorType `fmap` E.fromException e == + Just ResourceVanished + then f ++ " not found in path" + else show e -- | Data structure for command line options. data Opt = Opt @@ -113,7 +122,7 @@ data Opt = Opt , optTransforms :: [Pandoc -> Pandoc] -- ^ Doc transforms to apply , optTemplate :: Maybe FilePath -- ^ Custom template , optVariables :: [(String,String)] -- ^ Template variables to set - , optMetadata :: [(String,MetaValue)] -- ^ Metadata fields to set + , optMetadata :: M.Map String MetaValue -- ^ Metadata fields to set , optOutputFile :: String -- ^ Name of output file , optNumberSections :: Bool -- ^ Number sections in LaTeX , optNumberOffset :: [Int] -- ^ Starting number for sections @@ -140,7 +149,7 @@ data Opt = Opt , optReferenceLinks :: Bool -- ^ Use reference links in writing markdown, rst , optWrapText :: Bool -- ^ Wrap text , optColumns :: Int -- ^ Line length in characters - , optPlugins :: [[String] -> Pandoc -> IO Pandoc] -- ^ Plugins to apply + , optFilters :: [FilePath] -- ^ Filters to apply , optEmailObfuscation :: ObfuscationMethod , optIdentifierPrefix :: String , optIndentedCodeClasses :: [String] -- ^ Default classes for indented code blocks @@ -168,7 +177,7 @@ defaultOpts = Opt , optTransforms = [] , optTemplate = Nothing , optVariables = [] - , optMetadata = [] + , optMetadata = M.empty , optOutputFile = "-" -- "-" means stdout , optNumberSections = False , optNumberOffset = [0,0,0,0,0,0] @@ -195,7 +204,7 @@ defaultOpts = Opt , optReferenceLinks = False , optWrapText = True , optColumns = 72 - , optPlugins = [] + , optFilters = [] , optEmailObfuscation = JavascriptObfuscation , optIdentifierPrefix = "" , optIndentedCodeClasses = [] @@ -285,8 +294,7 @@ options = , Option "F" ["filter"] (ReqArg - (\arg opt -> return opt { optPlugins = externalFilter arg : - optPlugins opt }) + (\arg opt -> return opt { optFilters = arg : optFilters opt }) "PROGRAM") "" -- "External JSON filter" @@ -328,9 +336,10 @@ options = (ReqArg (\arg opt -> do let (key,val) = case break (`elem` ":=") arg of - (k,_:v) -> (k, MetaString v) + (k,_:v) -> (k, readMetaValue v) (k,_) -> (k, MetaBool True) - return opt{ optMetadata = (key,val) : optMetadata opt }) + return opt{ optMetadata = addMetadata key val + $ optMetadata opt }) "KEY[:VALUE]") "" @@ -452,8 +461,6 @@ options = , Option "" ["self-contained"] (NoArg (\opt -> return opt { optSelfContained = True, - optVariables = ("slidy-url","slidy") : - optVariables opt, optStandalone = True })) "" -- "Make slide shows include all the needed js and css" @@ -649,7 +656,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") @@ -657,29 +664,32 @@ options = , Option "" ["bibliography"] (ReqArg - (\arg opt -> - return opt{ optMetadata = ("bibliography",MetaString arg) : - optMetadata opt - , optPlugins = externalFilter "pandoc-citeproc" - : optPlugins opt - }) + (\arg opt -> return opt{ optMetadata = addMetadata + "bibliography" (readMetaValue arg) + $ optMetadata opt + , optVariables = + ("biblio-files", dropExtension arg) : + optVariables opt + }) "FILE") "" , Option "" ["csl"] (ReqArg (\arg opt -> - return opt{ optMetadata = ("csl", MetaString arg) : - optMetadata opt }) + return opt{ optMetadata = addMetadata "csl" + (readMetaValue arg) + $ optMetadata opt }) "FILE") "" , Option "" ["citation-abbreviations"] (ReqArg (\arg opt -> - return opt{ optMetadata = ("citation-abbreviations", - MetaString arg) : - optMetadata opt }) + return opt{ optMetadata = addMetadata + "citation-abbreviations" + (readMetaValue arg) + $ optMetadata opt }) "FILE") "" @@ -779,6 +789,20 @@ options = ] +addMetadata :: String -> MetaValue -> M.Map String MetaValue + -> M.Map String MetaValue +addMetadata k v m = case M.lookup k m of + Nothing -> M.insert k v m + Just (MetaList xs) -> M.insert k + (MetaList (xs ++ [v])) m + Just x -> M.insert k (MetaList [v, x]) m + +readMetaValue :: String -> MetaValue +readMetaValue s = case decode (UTF8.fromString s) of + Just (Yaml.String t) -> MetaString $ T.unpack t + Just (Yaml.Bool b) -> MetaBool b + _ -> MetaString s + -- Returns usage message usageMessage :: String -> [OptDescr (Opt -> IO Opt)] -> String usageMessage programName = usageInfo @@ -915,7 +939,7 @@ main = do , optReferenceLinks = referenceLinks , optWrapText = wrap , optColumns = columns - , optPlugins = plugins + , optFilters = filters , optEmailObfuscation = obfuscationMethod , optIdentifierPrefix = idPrefix , optIndentedCodeClasses = codeBlockClasses @@ -935,6 +959,15 @@ main = do mapM_ (\arg -> UTF8.hPutStrLn stdout arg) args exitWith ExitSuccess + -- --bibliography implies -F pandoc-citeproc for backwards compatibility: + let filters' = case M.lookup "bibliography" metadata of + Just _ | optCiteMethod opts /= Natbib && + optCiteMethod opts /= Biblatex && + all (\f -> takeBaseName f /= "pandoc-citeproc") + filters -> "pandoc-citeproc" : filters + _ -> filters + let plugins = map externalFilter filters' + let sources = if ignoreArgs then [] else args datadir <- case mbDataDir of @@ -954,7 +987,10 @@ main = do let writerName' = if null writerName then defaultWriterName outputFile - else writerName + else case writerName of + "epub2" -> "epub" + "html4" -> "html" + x -> x let pdfOutput = map toLower (takeExtension outputFile) == ".pdf" @@ -1003,12 +1039,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 @@ -1089,10 +1123,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) @@ -1105,7 +1142,7 @@ main = do reader readerOpts - let doc0 = foldr (\(k,v) -> setMeta k v) doc metadata + let doc0 = M.foldWithKey setMeta doc metadata let doc1 = foldr ($) doc0 transforms doc2 <- foldrM ($) doc1 $ map ($ [writerName']) plugins |