aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2019-10-09 12:44:09 -0700
committerJohn MacFarlane <jgm@berkeley.edu>2019-10-09 12:44:09 -0700
commit83702404af948ca7b36d2e0f11eb912997fa5800 (patch)
tree0d45e27e5287dc111909b1033e59cd5e0e160c3a /src/Text/Pandoc
parent5419988f225d1debcf9735f5de75a269db143bba (diff)
downloadpandoc-83702404af948ca7b36d2e0f11eb912997fa5800.tar.gz
Initial implementation of --defaults option.
Need documentation.
Diffstat (limited to 'src/Text/Pandoc')
-rw-r--r--src/Text/Pandoc/App/CommandLineOptions.hs25
-rw-r--r--src/Text/Pandoc/App/Opt.hs2
2 files changed, 24 insertions, 3 deletions
diff --git a/src/Text/Pandoc/App/CommandLineOptions.hs b/src/Text/Pandoc/App/CommandLineOptions.hs
index 9674a5aa0..e9582eaf2 100644
--- a/src/Text/Pandoc/App/CommandLineOptions.hs
+++ b/src/Text/Pandoc/App/CommandLineOptions.hs
@@ -42,7 +42,7 @@ import System.FilePath
import System.IO (stdout)
import Text.Pandoc
import Text.Pandoc.Builder (setMeta)
-import Text.Pandoc.App.Opt (Opt (..), LineEnding (..))
+import Text.Pandoc.App.Opt (Opt (..), LineEnding (..), defaultOpts)
import Text.Pandoc.Filter (Filter (..))
import Text.Pandoc.Highlighting (highlightingStyles)
import Text.Pandoc.Writers.Math (defaultMathJaxURL, defaultKaTeXURL)
@@ -64,6 +64,8 @@ import qualified Data.Text as T
import Data.Text (Text)
import Text.DocTemplates (ToContext(toVal), Context(..))
import qualified Text.Pandoc.UTF8 as UTF8
+import qualified Data.YAML.Aeson as YA
+import qualified Data.YAML as Y
parseOptions :: [OptDescr (Opt -> IO Opt)] -> Opt -> IO Opt
parseOptions options' defaults = do
@@ -108,7 +110,26 @@ pdfEngines = ordNub $ map snd engines
-- in response to a command-line option.
options :: [OptDescr (Opt -> IO Opt)]
options =
- [ Option "fr" ["from","read"]
+ [ Option "" ["defaults"]
+ (ReqArg
+ (\arg _opt -> do
+ let defaults = YA.encode1 defaultOpts
+ inp <- E.catch (B.readFile arg)
+ (\e -> E.throwIO $ PandocIOError
+ "Error reading defaults file" e)
+ case YA.decode1 (defaults <> inp) of
+ Right (newopts :: Opt) -> do
+ return newopts
+ Left (errpos, errmsg) -> E.throwIO $
+ PandocParseError $ "Error parsing " ++ arg ++
+ " (line " ++ show (Y.posLine errpos) ++
+ " column " ++ show (Y.posColumn errpos) ++ ")\n"
+ ++ errmsg
+ )
+ "FILE")
+ ""
+
+ , Option "fr" ["from","read"]
(ReqArg
(\arg opt -> return opt { optReader =
Just (map toLower arg) })
diff --git a/src/Text/Pandoc/App/Opt.hs b/src/Text/Pandoc/App/Opt.hs
index 3e90ec0d3..09086659d 100644
--- a/src/Text/Pandoc/App/Opt.hs
+++ b/src/Text/Pandoc/App/Opt.hs
@@ -184,7 +184,7 @@ defaultOpts = Opt
, optResourcePath = ["."]
, optRequestHeaders = []
, optEol = Native
- , optStripComments = False
+ , optStripComments = False
}
-- see https://github.com/jgm/pandoc/pull/4083