Implement environment variable interpolation in defaults files.
This allows the syntax `${HOME}` to be used, in fields that expect file paths only. Any environment variable may be interpolated in this way. A warning will be raised for undefined variables. The special variable `USERDATA` is automatically set to the user data directory in force when the defaults file is parsed. (Note: it may be different from the eventual user data directory, if the defaults file or further command line options change that.) Closes #5982. Closes #5977. Closes #6108 (path not taken).
This commit is contained in:
parent
a832469006
commit
6dd7520cc4
3 changed files with 147 additions and 14 deletions
15
MANUAL.txt
15
MANUAL.txt
|
@ -1672,6 +1672,21 @@ one line:
|
|||
verbosity: INFO
|
||||
```
|
||||
|
||||
In fields that expect a file path (or list of file paths), the
|
||||
following syntax may be used to interpolate environment variables:
|
||||
|
||||
``` yaml
|
||||
csl: ${HOME}/mycsldir/special.csl
|
||||
```
|
||||
|
||||
`${USERDATA}` may also be used; this will always resolve to the
|
||||
user data directory that is current when the defaults file is
|
||||
parsed, regardless of the setting of the environment
|
||||
variable `USERDATA`.
|
||||
|
||||
This environment variable interpolation syntax *only* works in
|
||||
fields that expect file paths.
|
||||
|
||||
Default files can be placed in the `defaults` subdirectory of
|
||||
the user data directory and used from any directory. For
|
||||
example, one could create a file specifying defaults for writing
|
||||
|
|
|
@ -47,10 +47,11 @@ import System.FilePath ( takeBaseName, takeExtension )
|
|||
import System.IO (nativeNewline, stdout)
|
||||
import qualified System.IO as IO (Newline (..))
|
||||
import Text.Pandoc
|
||||
import Text.Pandoc.Builder (setMeta)
|
||||
import Text.Pandoc.MIME (getCharset)
|
||||
import Text.Pandoc.App.FormatHeuristics (formatFromFilePaths)
|
||||
import Text.Pandoc.App.Opt (Opt (..), LineEnding (..), defaultOpts,
|
||||
IpynbOutput (..) )
|
||||
IpynbOutput (..))
|
||||
import Text.Pandoc.App.CommandLineOptions (parseOptions, parseOptionsFromArgs,
|
||||
options)
|
||||
import Text.Pandoc.App.OutputSettings (OutputSettings (..), optToOutputSettings)
|
||||
|
@ -60,7 +61,7 @@ import Text.Pandoc.PDF (makePDF)
|
|||
import Text.Pandoc.SelfContained (makeSelfContained)
|
||||
import Text.Pandoc.Shared (eastAsianLineBreakFilter, stripEmptyParagraphs,
|
||||
headerShift, isURI, tabFilter, uriPathToPath, filterIpynbOutput,
|
||||
defaultUserDataDirs, tshow, findM)
|
||||
defaultUserDataDir, tshow)
|
||||
import Text.Pandoc.Writers.Shared (lookupMetaString)
|
||||
import Text.Pandoc.Readers.Markdown (yamlToMeta)
|
||||
import qualified Text.Pandoc.UTF8 as UTF8
|
||||
|
@ -71,6 +72,15 @@ import System.Posix.Terminal (queryTerminal)
|
|||
|
||||
convertWithOpts :: Opt -> IO ()
|
||||
convertWithOpts opts = do
|
||||
datadir <- case optDataDir opts of
|
||||
Nothing -> do
|
||||
d <- defaultUserDataDir
|
||||
exists <- doesDirectoryExist d
|
||||
return $ if exists
|
||||
then Just d
|
||||
else Nothing
|
||||
Just _ -> return $ optDataDir opts
|
||||
|
||||
let outputFile = fromMaybe "-" (optOutputFile opts)
|
||||
let filters = optFilters opts
|
||||
let verbosity = optVerbosity opts
|
||||
|
@ -85,12 +95,6 @@ convertWithOpts opts = do
|
|||
Just xs | not (optIgnoreArgs opts) -> xs
|
||||
_ -> ["-"]
|
||||
|
||||
datadir <- case optDataDir opts of
|
||||
Nothing -> do
|
||||
ds <- defaultUserDataDirs
|
||||
findM doesDirectoryExist ds
|
||||
Just _ -> return $ optDataDir opts
|
||||
|
||||
let runIO' :: PandocIO a -> IO a
|
||||
runIO' f = do
|
||||
(res, reports) <- runIOorExplode $ do
|
||||
|
@ -275,12 +279,21 @@ convertWithOpts opts = do
|
|||
report $ Deprecated "pandoc-citeproc filter"
|
||||
"Use --citeproc instead."
|
||||
|
||||
let cslMetadata =
|
||||
maybe id (setMeta "csl") (optCSL opts) .
|
||||
(case optBibliography opts of
|
||||
[] -> id
|
||||
xs -> setMeta "bibliography" xs) .
|
||||
maybe id (setMeta "citation-abbreviations")
|
||||
(optCitationAbbreviations opts) $ mempty
|
||||
|
||||
doc <- sourceToDoc sources >>=
|
||||
( (if isJust (optExtractMedia opts)
|
||||
then fillMediaBag
|
||||
else return)
|
||||
>=> return . adjustMetadata (metadataFromFile <>)
|
||||
>=> return . adjustMetadata (<> optMetadata opts)
|
||||
>=> return . adjustMetadata (<> cslMetadata)
|
||||
>=> applyTransforms transforms
|
||||
>=> applyFilters readerOpts filters [T.unpack format]
|
||||
>=> maybe return extractMedia (optExtractMedia opts)
|
||||
|
|
|
@ -32,16 +32,18 @@ import Data.Char (isLower, toLower)
|
|||
import Data.Maybe (fromMaybe)
|
||||
import GHC.Generics hiding (Meta)
|
||||
import Text.Pandoc.Filter (Filter (..))
|
||||
import Text.Pandoc.Logging (Verbosity (WARNING))
|
||||
import Text.Pandoc.Logging (Verbosity (WARNING), LogMessage(..))
|
||||
import Text.Pandoc.Options (TopLevelDivision (TopLevelDefault),
|
||||
TrackChanges (AcceptChanges),
|
||||
WrapOption (WrapAuto), HTMLMathMethod (PlainMath),
|
||||
ReferenceLocation (EndOfDocument),
|
||||
ObfuscationMethod (NoObfuscation),
|
||||
CiteMethod (Citeproc))
|
||||
import Text.Pandoc.Class (readFileLazy, fileExists, setVerbosity, PandocMonad)
|
||||
import Text.Pandoc.Class (readFileLazy, fileExists, setVerbosity, report,
|
||||
PandocMonad(lookupEnv), getUserDataDir)
|
||||
import Text.Pandoc.Error (PandocError (PandocParseError, PandocSomeError))
|
||||
import Text.Pandoc.Shared (camelCaseStrToHyphenated, defaultUserDataDirs, findM, ordNub)
|
||||
import Text.Pandoc.Shared (camelCaseStrToHyphenated, defaultUserDataDir,
|
||||
findM, ordNub)
|
||||
import qualified Text.Pandoc.Parsing as P
|
||||
import Text.Pandoc.Readers.Metadata (yamlMap)
|
||||
import Text.Pandoc.Class.PandocPure
|
||||
|
@ -176,17 +178,120 @@ instance (PandocMonad m, MonadIO m)
|
|||
dataDir <- case M.lookup "data-dir" opts of
|
||||
Nothing -> return Nothing
|
||||
Just v -> Just . unpack <$> parseYAML v
|
||||
f <- parseOptions $ M.toList m
|
||||
f <- parseOptions (M.toList m)
|
||||
case M.lookup "defaults" opts of
|
||||
Just v -> do
|
||||
g <- parseDefaults v dataDir
|
||||
return $ g >=> f
|
||||
Nothing -> return f
|
||||
return $ g >=> f >=> resolveVarsInOpt
|
||||
Nothing -> return $ f >=> resolveVarsInOpt
|
||||
where
|
||||
toText (Scalar _ (SStr s)) = s
|
||||
toText _ = ""
|
||||
parseYAML n = failAtNode n "Expected a mapping"
|
||||
|
||||
resolveVarsInOpt :: (PandocMonad m, MonadIO m) => Opt -> m Opt
|
||||
resolveVarsInOpt
|
||||
opt@Opt
|
||||
{ optTemplate = oTemplate
|
||||
, optMetadataFiles = oMetadataFiles
|
||||
, optOutputFile = oOutputFile
|
||||
, optInputFiles = oInputFiles
|
||||
, optSyntaxDefinitions = oSyntaxDefinitions
|
||||
, optAbbreviations = oAbbreviations
|
||||
, optReferenceDoc = oReferenceDoc
|
||||
, optEpubMetadata = oEpubMetadata
|
||||
, optEpubFonts = oEpubFonts
|
||||
, optEpubCoverImage = oEpubCoverImage
|
||||
, optLogFile = oLogFile
|
||||
, optFilters = oFilters
|
||||
, optDataDir = oDataDir
|
||||
, optExtractMedia = oExtractMedia
|
||||
, optCss = oCss
|
||||
, optIncludeBeforeBody = oIncludeBeforeBody
|
||||
, optIncludeAfterBody = oIncludeAfterBody
|
||||
, optIncludeInHeader = oIncludeInHeader
|
||||
, optResourcePath = oResourcePath
|
||||
, optCSL = oCSL
|
||||
, optBibliography = oBibliography
|
||||
, optCitationAbbreviations = oCitationAbbreviations
|
||||
}
|
||||
= do
|
||||
oTemplate' <- mapM resolveVars oTemplate
|
||||
oMetadataFiles' <- mapM resolveVars oMetadataFiles
|
||||
oOutputFile' <- mapM resolveVars oOutputFile
|
||||
oInputFiles' <- mapM (mapM resolveVars) oInputFiles
|
||||
oSyntaxDefinitions' <- mapM resolveVars oSyntaxDefinitions
|
||||
oAbbreviations' <- mapM resolveVars oAbbreviations
|
||||
oReferenceDoc' <- mapM resolveVars oReferenceDoc
|
||||
oEpubMetadata' <- mapM resolveVars oEpubMetadata
|
||||
oEpubFonts' <- mapM resolveVars oEpubFonts
|
||||
oEpubCoverImage' <- mapM resolveVars oEpubCoverImage
|
||||
oLogFile' <- mapM resolveVars oLogFile
|
||||
oFilters' <- mapM resolveVarsInFilter oFilters
|
||||
oDataDir' <- mapM resolveVars oDataDir
|
||||
oExtractMedia' <- mapM resolveVars oExtractMedia
|
||||
oCss' <- mapM resolveVars oCss
|
||||
oIncludeBeforeBody' <- mapM resolveVars oIncludeBeforeBody
|
||||
oIncludeAfterBody' <- mapM resolveVars oIncludeAfterBody
|
||||
oIncludeInHeader' <- mapM resolveVars oIncludeInHeader
|
||||
oResourcePath' <- mapM resolveVars oResourcePath
|
||||
oCSL' <- mapM resolveVars oCSL
|
||||
oBibliography' <- mapM resolveVars oBibliography
|
||||
oCitationAbbreviations' <- mapM resolveVars oCitationAbbreviations
|
||||
return opt{ optTemplate = oTemplate'
|
||||
, optMetadataFiles = oMetadataFiles'
|
||||
, optOutputFile = oOutputFile'
|
||||
, optInputFiles = oInputFiles'
|
||||
, optSyntaxDefinitions = oSyntaxDefinitions'
|
||||
, optAbbreviations = oAbbreviations'
|
||||
, optReferenceDoc = oReferenceDoc'
|
||||
, optEpubMetadata = oEpubMetadata'
|
||||
, optEpubFonts = oEpubFonts'
|
||||
, optEpubCoverImage = oEpubCoverImage'
|
||||
, optLogFile = oLogFile'
|
||||
, optFilters = oFilters'
|
||||
, optDataDir = oDataDir'
|
||||
, optExtractMedia = oExtractMedia'
|
||||
, optCss = oCss'
|
||||
, optIncludeBeforeBody = oIncludeBeforeBody'
|
||||
, optIncludeAfterBody = oIncludeAfterBody'
|
||||
, optIncludeInHeader = oIncludeInHeader'
|
||||
, optResourcePath = oResourcePath'
|
||||
, optCSL = oCSL'
|
||||
, optBibliography = oBibliography'
|
||||
, optCitationAbbreviations = oCitationAbbreviations'
|
||||
}
|
||||
|
||||
where
|
||||
resolveVars [] = return []
|
||||
resolveVars ('$':'{':xs) =
|
||||
let (ys, zs) = break (=='}') xs
|
||||
in if null zs
|
||||
then return $ '$':'{':xs
|
||||
else do
|
||||
val <- lookupEnv' ys
|
||||
(val ++) <$> resolveVars (drop 1 zs)
|
||||
resolveVars (c:cs) = (c:) <$> resolveVars cs
|
||||
lookupEnv' "USERDATA" = do
|
||||
mbodatadir <- mapM resolveVars oDataDir
|
||||
mbdatadir <- getUserDataDir
|
||||
defdatadir <- liftIO defaultUserDataDir
|
||||
return $ fromMaybe defdatadir (mbodatadir <|> mbdatadir)
|
||||
lookupEnv' v = do
|
||||
mbval <- fmap T.unpack <$> lookupEnv (T.pack v)
|
||||
case mbval of
|
||||
Nothing -> do
|
||||
report $ EnvironmentVariableUndefined (T.pack v)
|
||||
return mempty
|
||||
Just x -> return x
|
||||
resolveVarsInFilter (JSONFilter fp) =
|
||||
JSONFilter <$> resolveVars fp
|
||||
resolveVarsInFilter (LuaFilter fp) =
|
||||
LuaFilter <$> resolveVars fp
|
||||
resolveVarsInFilter CiteprocFilter = return CiteprocFilter
|
||||
|
||||
|
||||
|
||||
parseDefaults :: (PandocMonad m, MonadIO m)
|
||||
=> Node Pos
|
||||
-> Maybe FilePath
|
||||
|
|
Loading…
Add table
Reference in a new issue