aboutsummaryrefslogtreecommitdiff
path: root/src
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2021-03-05 10:42:33 -0800
committerJohn MacFarlane <jgm@berkeley.edu>2021-03-05 10:42:33 -0800
commita8324690061d561583f2cb583cfb28591f500181 (patch)
treee704bd6628dbae44cc18e046e8425886ba2473bc /src
parentccc530c5884f9c36d63fb8a63ce6fadce166015c (diff)
downloadpandoc-a8324690061d561583f2cb583cfb28591f500181.tar.gz
Add fields for CSL optinos to Opt.
* Add `optCSL`, `optBibliography`, `optCitationAbbreviations` to `Opt` [API change]. * Move `addMeta` from T.P.App.Opt to T.P.App.CommandLineOptions.
Diffstat (limited to 'src')
-rw-r--r--src/Text/Pandoc/App/CommandLineOptions.hs31
-rw-r--r--src/Text/Pandoc/App/Opt.hs68
2 files changed, 46 insertions, 53 deletions
diff --git a/src/Text/Pandoc/App/CommandLineOptions.hs b/src/Text/Pandoc/App/CommandLineOptions.hs
index 0a8193f6c..ac92db0ae 100644
--- a/src/Text/Pandoc/App/CommandLineOptions.hs
+++ b/src/Text/Pandoc/App/CommandLineOptions.hs
@@ -48,12 +48,13 @@ import System.FilePath
import System.IO (stdout)
import Text.DocTemplates (Context (..), ToContext (toVal), Val (..))
import Text.Pandoc
+import Text.Pandoc.Builder (setMeta)
import Text.Pandoc.App.Opt (Opt (..), LineEnding (..), IpynbOutput (..),
- DefaultsState (..), addMeta, applyDefaults,
+ DefaultsState (..), applyDefaults,
fullDefaultsPath)
import Text.Pandoc.Filter (Filter (..))
import Text.Pandoc.Highlighting (highlightingStyles)
-import Text.Pandoc.Shared (ordNub, elemText, safeStrRead, defaultUserDataDirs)
+import Text.Pandoc.Shared (ordNub, elemText, safeStrRead, defaultUserDataDir)
import Text.Printf
#ifdef EMBED_DATA_FILES
@@ -939,13 +940,12 @@ options =
(NoArg
(\_ -> do
prg <- getProgName
- defaultDatadirs <- defaultUserDataDirs
+ defaultDatadir <- defaultUserDataDir
UTF8.hPutStrLn stdout
$ T.pack
$ prg ++ " " ++ T.unpack pandocVersion ++
compileInfo ++
- "\nUser data directory: " ++
- intercalate " or " defaultDatadirs ++
+ "\nUser data directory: " ++ defaultDatadir ++
('\n':copyrightMessage)
exitSuccess ))
"" -- "Print version"
@@ -1053,6 +1053,27 @@ 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 0d96ab67c..b69e4e51e 100644
--- a/src/Text/Pandoc/App/Opt.hs
+++ b/src/Text/Pandoc/App/Opt.hs
@@ -22,7 +22,6 @@ module Text.Pandoc.App.Opt (
, IpynbOutput (..)
, DefaultsState (..)
, defaultOpts
- , addMeta
, applyDefaults
, fullDefaultsPath
) where
@@ -32,7 +31,6 @@ import System.FilePath ( addExtension, (</>), takeExtension )
import Data.Char (isLower, toLower)
import Data.Maybe (fromMaybe)
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),
@@ -52,7 +50,7 @@ import Data.Text (Text, unpack)
import Data.Default (def)
import qualified Data.Text as T
import qualified Data.Map as M
-import Text.Pandoc.Definition (Meta(..), MetaValue(..), lookupMeta)
+import Text.Pandoc.Definition (Meta(..), MetaValue(..))
import Data.Aeson (defaultOptions, Options(..))
import Data.Aeson.TH (deriveJSON)
import Control.Applicative ((<|>))
@@ -156,6 +154,9 @@ data Opt = Opt
, optNoCheckCertificate :: Bool -- ^ Disable certificate validation
, optEol :: LineEnding -- ^ Style of line-endings to use
, optStripComments :: Bool -- ^ Skip HTML comments
+ , optCSL :: Maybe FilePath -- ^ CSL stylesheet
+ , optBibliography :: [FilePath] -- ^ Bibliography files
+ , optCitationAbbreviations :: Maybe FilePath -- ^ Citation abbreviations
} deriving (Generic, Show)
instance FromYAML (Opt -> Opt) where
@@ -428,26 +429,18 @@ 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)
+ (parseYAML v >>= \x -> return (\o ->
+ o{ optBibliography = optBibliography o <>
+ map unpack x }))
+ <|>
+ (parseYAML v >>= \x -> return (\o ->
+ o{ optBibliography = optBibliography o <>
+ [unpack x] }))
"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)
+ parseYAML v >>= \x -> return (\o -> o{ optCSL = unpack <$> x })
"citation-abbreviations" ->
- parseYAML v >>= \x ->
- return (\o -> o{ optMetadata =
- addMeta "citation-abbreviations" (T.unpack x)
- (optMetadata o) })
+ parseYAML v >>= \x -> return (\o -> o{ optCitationAbbreviations =
+ unpack <$> x })
"ipynb-output" ->
parseYAML v >>= \x -> return (\o -> o{ optIpynbOutput = x })
"include-before-body" ->
@@ -562,6 +555,9 @@ defaultOpts = Opt
, optNoCheckCertificate = False
, optEol = Native
, optStripComments = False
+ , optCSL = Nothing
+ , optBibliography = []
+ , optCitationAbbreviations = Nothing
}
parseStringKey :: Node Pos -> Parser Text
@@ -579,27 +575,6 @@ yamlToMeta (Mapping _ _ m) =
>>= fmap (Meta . flip P.runF def)
yamlToMeta _ = return mempty
-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
-
-- | Apply defaults from --defaults file.
applyDefaults :: (PandocMonad m, MonadIO m)
=> Opt
@@ -625,12 +600,9 @@ fullDefaultsPath dataDir file = do
let fp = if null (takeExtension file)
then addExtension file "yaml"
else file
- dataDirs <- liftIO defaultUserDataDirs
- let fps = fp : case dataDir of
- Nothing -> map (</> ("defaults" </> fp))
- dataDirs
- Just dd -> [dd </> "defaults" </> fp]
- fromMaybe fp <$> findM fileExists fps
+ defaultDataDir <- liftIO defaultUserDataDir
+ let defaultFp = fromMaybe defaultDataDir dataDir </> "defaults" </> fp
+ fromMaybe fp <$> findM fileExists [fp, defaultFp]
-- | In a list of lists, append another list in front of every list which
-- starts with specific element.