aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/App
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/App')
-rw-r--r--src/Text/Pandoc/App/CommandLineOptions.hs5
-rw-r--r--src/Text/Pandoc/App/Opt.hs4
-rw-r--r--src/Text/Pandoc/App/OutputSettings.hs22
3 files changed, 30 insertions, 1 deletions
diff --git a/src/Text/Pandoc/App/CommandLineOptions.hs b/src/Text/Pandoc/App/CommandLineOptions.hs
index d2c12573c..99017000a 100644
--- a/src/Text/Pandoc/App/CommandLineOptions.hs
+++ b/src/Text/Pandoc/App/CommandLineOptions.hs
@@ -188,6 +188,11 @@ options =
(\opt -> return opt { optFileScope = True }))
"" -- "Parse input files before combining"
+ , Option "" ["sandbox"]
+ (NoArg
+ (\opt -> return opt { optSandbox = True }))
+ ""
+
, Option "s" ["standalone"]
(NoArg
(\opt -> return opt { optStandalone = True }))
diff --git a/src/Text/Pandoc/App/Opt.hs b/src/Text/Pandoc/App/Opt.hs
index d54d932b7..48eb15fdf 100644
--- a/src/Text/Pandoc/App/Opt.hs
+++ b/src/Text/Pandoc/App/Opt.hs
@@ -160,6 +160,7 @@ data Opt = Opt
, optCSL :: Maybe FilePath -- ^ CSL stylesheet
, optBibliography :: [FilePath] -- ^ Bibliography files
, optCitationAbbreviations :: Maybe FilePath -- ^ Citation abbreviations
+ , optSandbox :: Bool
} deriving (Generic, Show)
instance FromYAML (Opt -> Opt) where
@@ -595,6 +596,8 @@ doOpt (k',v) = do
parseYAML v >>= \x -> return (\o -> o{ optEol = x })
"strip-comments" ->
parseYAML v >>= \x -> return (\o -> o { optStripComments = x })
+ "sandbox" ->
+ parseYAML v >>= \x -> return (\o -> o { optSandbox = x })
_ -> failAtNode k' $ "Unknown option " ++ show k
-- | Defaults for command-line options.
@@ -673,6 +676,7 @@ defaultOpts = Opt
, optCSL = Nothing
, optBibliography = []
, optCitationAbbreviations = Nothing
+ , optSandbox = False
}
parseStringKey :: Node Pos -> Parser Text
diff --git a/src/Text/Pandoc/App/OutputSettings.hs b/src/Text/Pandoc/App/OutputSettings.hs
index 3f83f4b21..7b057713b 100644
--- a/src/Text/Pandoc/App/OutputSettings.hs
+++ b/src/Text/Pandoc/App/OutputSettings.hs
@@ -90,11 +90,31 @@ optToOutputSettings opts = do
then writerName
else T.toLower $ baseWriterName writerName
+ let makeSandboxed pureWriter =
+ let files = maybe id (:) (optReferenceDoc opts) .
+ maybe id (:) (optEpubMetadata opts) .
+ maybe id (:) (optEpubCoverImage opts) .
+ maybe id (:) (optCSL opts) .
+ maybe id (:) (optCitationAbbreviations opts) $
+ optEpubFonts opts ++
+ optBibliography opts
+ in case pureWriter of
+ TextWriter w -> TextWriter $ \o d -> sandbox files (w o d)
+ ByteStringWriter w
+ -> ByteStringWriter $ \o d -> sandbox files (w o d)
+
+
(writer, writerExts) <-
if ".lua" `T.isSuffixOf` format
then return (TextWriter
(\o d -> writeCustom (T.unpack writerName) o d), mempty)
- else getWriter (T.toLower writerName)
+ else if optSandbox opts
+ then
+ case runPure (getWriter writerName) of
+ Left e -> throwError e
+ Right (w, wexts) ->
+ return (makeSandboxed w, wexts)
+ else getWriter (T.toLower writerName)
let standalone = optStandalone opts || not (isTextFormat format) || pdfOutput