Pass writename as argument to filters.
This way filters can figure out what the target format is and react appropriately. Example: #!/usr/bin/env runghc import Text.Pandoc.JSON import Data.Char main = toJSONFilter cap where cap (Just "html") (Str xs) = Str $ map toUpper xs cap _ x = x This capitalizes text only for html output.
This commit is contained in:
parent
83f263110f
commit
99bb066bb9
3 changed files with 13 additions and 11 deletions
|
@ -352,8 +352,8 @@ Executable pandoc
|
||||||
bytestring >= 0.9 && < 0.11,
|
bytestring >= 0.9 && < 0.11,
|
||||||
extensible-exceptions >= 0.1 && < 0.2,
|
extensible-exceptions >= 0.1 && < 0.2,
|
||||||
highlighting-kate >= 0.5.5 && < 0.6,
|
highlighting-kate >= 0.5.5 && < 0.6,
|
||||||
|
aeson >= 0.6 && < 0.7,
|
||||||
HTTP >= 4000.0.5 && < 4000.3,
|
HTTP >= 4000.0.5 && < 4000.3,
|
||||||
process >= 1 && < 1.2,
|
|
||||||
citeproc-hs >= 0.3.7 && < 0.4
|
citeproc-hs >= 0.3.7 && < 0.4
|
||||||
Ghc-Options: -rtsopts -with-rtsopts=-K16m -Wall -fno-warn-unused-do-bind
|
Ghc-Options: -rtsopts -with-rtsopts=-K16m -Wall -fno-warn-unused-do-bind
|
||||||
Ghc-Prof-Options: -auto-all -caf-all -rtsopts -with-rtsopts=-K16m
|
Ghc-Prof-Options: -auto-all -caf-all -rtsopts -with-rtsopts=-K16m
|
||||||
|
|
17
pandoc.hs
17
pandoc.hs
|
@ -37,13 +37,13 @@ import Text.Pandoc.Shared ( tabFilter, readDataFileUTF8, safeRead,
|
||||||
headerShift, normalize, err, warn )
|
headerShift, normalize, err, warn )
|
||||||
import Text.Pandoc.XML ( toEntities, fromEntities )
|
import Text.Pandoc.XML ( toEntities, fromEntities )
|
||||||
import Text.Pandoc.SelfContained ( makeSelfContained )
|
import Text.Pandoc.SelfContained ( makeSelfContained )
|
||||||
|
import Text.Pandoc.Process (pipeProcess)
|
||||||
import Text.Highlighting.Kate ( languages, Style, tango, pygments,
|
import Text.Highlighting.Kate ( languages, Style, tango, pygments,
|
||||||
espresso, zenburn, kate, haddock, monochrome )
|
espresso, zenburn, kate, haddock, monochrome )
|
||||||
import System.Environment ( getArgs, getProgName )
|
import System.Environment ( getArgs, getProgName )
|
||||||
import System.Exit ( exitWith, ExitCode (..) )
|
import System.Exit ( exitWith, ExitCode (..) )
|
||||||
import System.FilePath
|
import System.FilePath
|
||||||
import System.Console.GetOpt
|
import System.Console.GetOpt
|
||||||
import System.Process (readProcess)
|
|
||||||
import Data.Char ( toLower )
|
import Data.Char ( toLower )
|
||||||
import Data.List ( intercalate, isPrefixOf, sort )
|
import Data.List ( intercalate, isPrefixOf, sort )
|
||||||
import System.Directory ( getAppUserDataDirectory, doesFileExist, findExecutable )
|
import System.Directory ( getAppUserDataDirectory, doesFileExist, findExecutable )
|
||||||
|
@ -59,6 +59,7 @@ import Network.HTTP (simpleHTTP, mkRequest, getResponseBody, RequestMethod(..))
|
||||||
import Network.URI (parseURI, isURI, URI(..))
|
import Network.URI (parseURI, isURI, URI(..))
|
||||||
import qualified Data.ByteString.Lazy as B
|
import qualified Data.ByteString.Lazy as B
|
||||||
import Text.CSL.Reference (Reference(..))
|
import Text.CSL.Reference (Reference(..))
|
||||||
|
import Data.Aeson (eitherDecode', encode)
|
||||||
|
|
||||||
copyrightMessage :: String
|
copyrightMessage :: String
|
||||||
copyrightMessage = "\nCopyright (C) 2006-2013 John MacFarlane\n" ++
|
copyrightMessage = "\nCopyright (C) 2006-2013 John MacFarlane\n" ++
|
||||||
|
@ -88,9 +89,13 @@ wrapWords indent c = wrap' (c - indent) (c - indent)
|
||||||
isTextFormat :: String -> Bool
|
isTextFormat :: String -> Bool
|
||||||
isTextFormat s = takeWhile (`notElem` "+-") s `notElem` ["odt","docx","epub","epub3"]
|
isTextFormat s = takeWhile (`notElem` "+-") s `notElem` ["odt","docx","epub","epub3"]
|
||||||
|
|
||||||
externalFilter :: FilePath -> Pandoc -> IO Pandoc
|
externalFilter :: FilePath -> [String] -> Pandoc -> IO Pandoc
|
||||||
externalFilter f d = E.catch
|
externalFilter f args' d = E.catch
|
||||||
(readJSON def `fmap` readProcess f [] (writeJSON def d))
|
(do (exitcode, outbs, errbs) <- pipeProcess Nothing f args' $ encode d
|
||||||
|
case exitcode of
|
||||||
|
ExitSuccess -> return $ either error id $ eitherDecode' outbs
|
||||||
|
ExitFailure _ -> err 83 $ "Error running filter `" ++ UTF8.toStringLazy outbs ++
|
||||||
|
UTF8.toStringLazy errbs ++ "'")
|
||||||
(\e -> let _ = (e :: E.SomeException)
|
(\e -> let _ = (e :: E.SomeException)
|
||||||
in err 83 $ "Error running filter `" ++ f ++ "'")
|
in err 83 $ "Error running filter `" ++ f ++ "'")
|
||||||
|
|
||||||
|
@ -132,7 +137,7 @@ data Opt = Opt
|
||||||
, optReferenceLinks :: Bool -- ^ Use reference links in writing markdown, rst
|
, optReferenceLinks :: Bool -- ^ Use reference links in writing markdown, rst
|
||||||
, optWrapText :: Bool -- ^ Wrap text
|
, optWrapText :: Bool -- ^ Wrap text
|
||||||
, optColumns :: Int -- ^ Line length in characters
|
, optColumns :: Int -- ^ Line length in characters
|
||||||
, optPlugins :: [Pandoc -> IO Pandoc] -- ^ Plugins to apply
|
, optPlugins :: [[String] -> Pandoc -> IO Pandoc] -- ^ Plugins to apply
|
||||||
, optEmailObfuscation :: ObfuscationMethod
|
, optEmailObfuscation :: ObfuscationMethod
|
||||||
, optIdentifierPrefix :: String
|
, optIdentifierPrefix :: String
|
||||||
, optIndentedCodeClasses :: [String] -- ^ Default classes for indented code blocks
|
, optIndentedCodeClasses :: [String] -- ^ Default classes for indented code blocks
|
||||||
|
@ -1115,7 +1120,7 @@ main = do
|
||||||
reader readerOpts
|
reader readerOpts
|
||||||
|
|
||||||
let doc0 = foldr ($) doc transforms
|
let doc0 = foldr ($) doc transforms
|
||||||
doc1 <- foldrM ($) doc0 plugins
|
doc1 <- foldrM ($) doc0 $ map ($ [writerName']) plugins
|
||||||
|
|
||||||
let writeBinary :: B.ByteString -> IO ()
|
let writeBinary :: B.ByteString -> IO ()
|
||||||
writeBinary = B.writeFile (UTF8.encodePath outputFile)
|
writeBinary = B.writeFile (UTF8.encodePath outputFile)
|
||||||
|
|
|
@ -309,11 +309,8 @@ class ToJSONFilter a => ToJsonFilter a
|
||||||
toJsonFilter = toJSONFilter
|
toJsonFilter = toJSONFilter
|
||||||
|
|
||||||
readJSON :: ReaderOptions -> String -> Pandoc
|
readJSON :: ReaderOptions -> String -> Pandoc
|
||||||
readJSON _ = checkJSON . eitherDecode' . UTF8.fromStringLazy
|
readJSON _ = either error id . eitherDecode' . UTF8.fromStringLazy
|
||||||
|
|
||||||
writeJSON :: WriterOptions -> Pandoc -> String
|
writeJSON :: WriterOptions -> Pandoc -> String
|
||||||
writeJSON _ = UTF8.toStringLazy . encode
|
writeJSON _ = UTF8.toStringLazy . encode
|
||||||
|
|
||||||
checkJSON :: Either String a -> a
|
|
||||||
checkJSON (Right x) = x
|
|
||||||
checkJSON (Left e) = error e
|
|
||||||
|
|
Loading…
Reference in a new issue