aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/App
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2020-01-31 21:55:36 -0800
committerJohn MacFarlane <jgm@berkeley.edu>2020-01-31 21:56:28 -0800
commit22f484e9a9ab94109380e217b6ff88317bb72741 (patch)
treee5ec186d1502bb2f2da28ef4e3178a88d4f65cc2 /src/Text/Pandoc/App
parentfb3df6cf19626f4936d9d984ef25ca54a4f85768 (diff)
downloadpandoc-22f484e9a9ab94109380e217b6ff88317bb72741.tar.gz
Support 'bibliography' and 'csl' fields in defaults file.
Move addMeta from T.P.App.CommandLineOptions to T.P.App.Opt. (not an api change because modules not exported)
Diffstat (limited to 'src/Text/Pandoc/App')
-rw-r--r--src/Text/Pandoc/App/CommandLineOptions.hs24
-rw-r--r--src/Text/Pandoc/App/Opt.hs42
2 files changed, 42 insertions, 24 deletions
diff --git a/src/Text/Pandoc/App/CommandLineOptions.hs b/src/Text/Pandoc/App/CommandLineOptions.hs
index 55ce17bd8..be6bc66f1 100644
--- a/src/Text/Pandoc/App/CommandLineOptions.hs
+++ b/src/Text/Pandoc/App/CommandLineOptions.hs
@@ -44,8 +44,7 @@ import System.FilePath
import System.IO (stdout)
import Text.DocTemplates (Val(..))
import Text.Pandoc
-import Text.Pandoc.Builder (setMeta)
-import Text.Pandoc.App.Opt (Opt (..), LineEnding (..), IpynbOutput (..))
+import Text.Pandoc.App.Opt (Opt (..), LineEnding (..), IpynbOutput (..), addMeta)
import Text.Pandoc.Filter (Filter (..))
import Text.Pandoc.Highlighting (highlightingStyles)
import Text.Pandoc.Shared (ordNub, elemText, safeStrRead, defaultUserDataDirs)
@@ -1037,27 +1036,6 @@ setVariable key val (Context ctx) = Context $ M.alter go key ctx
go (Just (ListVal xs)) = Just $ ListVal $ xs ++ [toVal val]
go (Just x) = Just $ ListVal [x, toVal val]
-addMeta :: String -> String -> Meta -> Meta
-addMeta k v meta =
- case lookupMeta k' meta of
- Nothing -> setMeta k' v' meta
- Just (MetaList xs) ->
- setMeta k' (MetaList (xs ++ [v'])) meta
- Just x -> setMeta k' (MetaList [x, v']) meta
- where
- v' = readMetaValue v
- k' = T.pack k
-
-readMetaValue :: String -> MetaValue
-readMetaValue s
- | s == "true" = MetaBool True
- | s == "True" = MetaBool True
- | s == "TRUE" = MetaBool True
- | s == "false" = MetaBool False
- | s == "False" = MetaBool False
- | s == "FALSE" = MetaBool False
- | otherwise = MetaString $ T.pack s
-
-- On Windows with ghc 8.6+, we need to rewrite paths
-- beginning with \\ to \\?\UNC\. -- See #5127.
normalizePath :: FilePath -> FilePath
diff --git a/src/Text/Pandoc/App/Opt.hs b/src/Text/Pandoc/App/Opt.hs
index a753d6ab3..2be0bb0d8 100644
--- a/src/Text/Pandoc/App/Opt.hs
+++ b/src/Text/Pandoc/App/Opt.hs
@@ -21,10 +21,12 @@ module Text.Pandoc.App.Opt (
, LineEnding (..)
, IpynbOutput (..)
, defaultOpts
+ , addMeta
) where
import Prelude
import Data.Char (isLower, toLower)
import GHC.Generics hiding (Meta)
+import Text.Pandoc.Builder (setMeta)
import Text.Pandoc.Filter (Filter (..))
import Text.Pandoc.Logging (Verbosity (WARNING))
import Text.Pandoc.Options (TopLevelDivision (TopLevelDefault),
@@ -39,7 +41,7 @@ import Text.DocTemplates (Context(..), Val(..))
import Data.Text (Text, unpack)
import qualified Data.Text as T
import qualified Data.Map as M
-import Text.Pandoc.Definition (Meta(..), MetaValue(..))
+import Text.Pandoc.Definition (Meta(..), MetaValue(..), lookupMeta)
import Data.Aeson (defaultOptions, Options(..))
import Data.Aeson.TH (deriveJSON)
import Control.Applicative ((<|>))
@@ -342,6 +344,22 @@ doOpt (k',v) = do
<|>
(parseYAML v >>= \x -> return (\o -> o{ optCss = optCss o <>
[unpack x] }))
+ "bibliography" ->
+ do let addItem x o = o{ optMetadata =
+ addMeta "bibliography" (T.unpack x)
+ (optMetadata o) }
+ (parseYAML v >>= \(xs :: [Text]) -> return $ \o ->
+ foldr addItem o xs)
+ <|>
+ (parseYAML v >>= \(x :: Text) -> return $ \o -> addItem x o)
+ "csl" ->
+ do let addItem x o = o{ optMetadata =
+ addMeta "csl" (T.unpack x)
+ (optMetadata o) }
+ (parseYAML v >>= \(xs :: [Text]) -> return $ \o ->
+ foldr addItem o xs)
+ <|>
+ (parseYAML v >>= \(x :: Text) -> return $ \o -> addItem x o)
"ipynb-output" ->
parseYAML v >>= \x -> return (\o -> o{ optIpynbOutput = x })
"include-before-body" ->
@@ -465,6 +483,28 @@ valToMetaVal (ListVal xs) = MetaList $ map valToMetaVal xs
valToMetaVal (SimpleVal d) = MetaString $ render Nothing d
valToMetaVal NullVal = MetaString ""
+addMeta :: String -> String -> Meta -> Meta
+addMeta k v meta =
+ case lookupMeta k' meta of
+ Nothing -> setMeta k' v' meta
+ Just (MetaList xs) ->
+ setMeta k' (MetaList (xs ++ [v'])) meta
+ Just x -> setMeta k' (MetaList [x, v']) meta
+ where
+ v' = readMetaValue v
+ k' = T.pack k
+
+readMetaValue :: String -> MetaValue
+readMetaValue s
+ | s == "true" = MetaBool True
+ | s == "True" = MetaBool True
+ | s == "TRUE" = MetaBool True
+ | s == "false" = MetaBool False
+ | s == "False" = MetaBool False
+ | s == "FALSE" = MetaBool False
+ | otherwise = MetaString $ T.pack s
+
+
-- see https://github.com/jgm/pandoc/pull/4083
-- using generic deriving caused long compilation times
$(deriveJSON