aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/App.hs
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2017-09-15 17:26:14 -0700
committerJohn MacFarlane <jgm@berkeley.edu>2017-09-15 17:26:14 -0700
commit684f0552489936427d4273b73ea55b6039a59751 (patch)
treea02d3c91ab34456810d4034166d061147850c13f /src/Text/Pandoc/App.hs
parent04aba6bd519f7dcfedd8947c6273fd59431a205c (diff)
downloadpandoc-684f0552489936427d4273b73ea55b6039a59751.tar.gz
Set PANDOC_READER_OPTIONS in environment where filters are run.
This contains a JSON representation of ReaderOptions.
Diffstat (limited to 'src/Text/Pandoc/App.hs')
-rw-r--r--src/Text/Pandoc/App.hs23
1 files changed, 16 insertions, 7 deletions
diff --git a/src/Text/Pandoc/App.hs b/src/Text/Pandoc/App.hs
index 3df4953f1..f8e23b10c 100644
--- a/src/Text/Pandoc/App.hs
+++ b/src/Text/Pandoc/App.hs
@@ -521,7 +521,7 @@ convertWithOpts opts = do
>=> return . flip (foldr addMetadata) metadata
>=> applyTransforms transforms
>=> applyLuaFilters datadir (optLuaFilters opts) [format]
- >=> applyFilters datadir filters' [format]
+ >=> applyFilters readerOpts datadir filters' [format]
)
media <- getMediaBag
@@ -560,8 +560,9 @@ type Transform = Pandoc -> Pandoc
isTextFormat :: String -> Bool
isTextFormat s = s `notElem` ["odt","docx","epub","epub3"]
-externalFilter :: MonadIO m => FilePath -> [String] -> Pandoc -> m Pandoc
-externalFilter f args' d = liftIO $ do
+externalFilter :: MonadIO m
+ => ReaderOptions -> FilePath -> [String] -> Pandoc -> m Pandoc
+externalFilter ropts f args' d = liftIO $ do
exists <- doesFileExist f
isExecutable <- if exists
then executable <$> getPermissions f
@@ -582,7 +583,10 @@ externalFilter f args' d = liftIO $ do
when (isNothing mbExe) $
E.throwIO $ PandocFilterError f ("Could not find executable " ++ f')
env <- getEnvironment
- let env' = Just $ ("PANDOC_VERSION", pandocVersion) : env
+ let env' = Just
+ ( ("PANDOC_VERSION", pandocVersion)
+ : ("PANDOC_READER_OPTIONS", UTF8.toStringLazy (encode ropts))
+ : env )
(exitcode, outbs) <- E.handle filterException $
pipeProcess env' f' args'' $ encode d
case exitcode of
@@ -862,10 +866,15 @@ applyLuaFilters mbDatadir filters args d = do
foldrM ($) d $ map go expandedFilters
applyFilters :: MonadIO m
- => Maybe FilePath -> [FilePath] -> [String] -> Pandoc -> m Pandoc
-applyFilters mbDatadir filters args d = do
+ => ReaderOptions
+ -> Maybe FilePath
+ -> [FilePath]
+ -> [String]
+ -> Pandoc
+ -> m Pandoc
+applyFilters ropts mbDatadir filters args d = do
expandedFilters <- mapM (expandFilterPath mbDatadir) filters
- foldrM ($) d $ map (flip externalFilter args) expandedFilters
+ foldrM ($) d $ map (flip (externalFilter ropts) args) expandedFilters
readSource :: FilePath -> PandocIO Text
readSource "-" = liftIO (UTF8.toText <$> BS.getContents)