Added --data-dir option.

+ This specifies a user data directory. If not specified, will default
  to ~/.pandoc on unix or Application Data\pandoc on Windows.
  Files placed in the user data directory will override system default
  data files.
+ Added datadir parameter to readDataFile, saveOpenDocumentAsODT,
  latexMathMLScript, s5HeaderIncludes, and getTemplate.  Removed
  getDefaultTemplate.
+ Updated documentation.

git-svn-id: https://pandoc.googlecode.com/svn/trunk@1809 788f1e2b-df1e-0410-8736-df70ead52e1b
This commit is contained in:
fiddlosopher 2010-01-14 05:54:38 +00:00
parent 385dcb116c
commit eb851a41ca
8 changed files with 99 additions and 89 deletions

55
README
View file

@ -330,16 +330,9 @@ For further documentation, see the `pandoc(1)` man page.
of an ODT produced using pandoc. The contents of the reference ODT
are ignored, but its stylesheets are used in the new ODT. If no
reference ODT is specified on the command line, pandoc will look
for a file `reference.odt` in
$HOME/.pandoc
(on unix) or
C:\Documents And Settings\USERNAME\Application Data\pandoc
(on Windows). If this is not found either, sensible defaults will be
used.
for a file `reference.odt` in the user data directory (see
`--data-dir`, below). If it is not found there, sensible defaults
will be used.
`-D` or `--print-default-template` *format*
: prints the default template for an output *format*. (See `-t`
@ -432,6 +425,20 @@ For further documentation, see the `pandoc(1)` man page.
`perl,numberLines` or `haskell`. Multiple classes may be separated
by spaces or commas.
`--data-dir`*=directory*
: specifies the user data directory to search for pandoc data files.
If this option is not specified, the default user data directory
will be used:
$HOME/.pandoc
in unix and
C:\Documents And Settings\USERNAME\Application Data\pandoc
in Windows. A reference ODT, `templates` directory, `s5` directory
placed in this directory will override pandoc's normal defaults.
`--dump-args`
: is intended to make it easier to create wrapper scripts that use
Pandoc. It causes Pandoc to dump information about the arguments
@ -483,15 +490,8 @@ document. To see the default template that is used, just type
where `FORMAT` is the name of the output format. A custom template
can be specified using the `--template` option. You can also override
the system default templates for a given output format `FORMAT`
by putting a file `FORMAT.template` in
$HOME/.pandoc/templates
(on unix) or
C:\Documents And Settings\USERNAME\Application Data\pandoc\templates
(on Windows).
by putting a file `templates/FORMAT.template` in the user data
directory (see `--data-dir`, above).
Templates may contain *variables*. Variable names are sequences of
alphanumerics, `-`, and `_`, starting with a letter. A variable name
@ -1231,18 +1231,11 @@ Alternatively, you may use `-s` together with the `--template`
option to specify a custom template.
You can change the style of the slides by putting customized CSS files
in
$HOME/.pandoc/s5/default
(on unix) or
C:\Documents And Settings\USERNAME\Application Data\pandoc\reference.odt
(on Windows). The originals may be found in pandoc's system
data directory (generally `$CABALDIR/pandoc-VERSION/s5/default`).
Pandoc will look there for any files it does not find in the user's
pandoc data directory.
in `$DATADIR/s5/default`, where `$DATADIR` is the user data directory
(see `--data-dir`, above). The originals may be found in pandoc's system
data directory (generally `$CABALDIR/pandoc-VERSION/s5/default`). Pandoc
will look there for any files it does not find in the user data
directory.
Literate Haskell support
========================

View file

@ -207,9 +207,8 @@ to Pandoc. Or use `html2markdown`(1), a wrapper around `pandoc`.
of an ODT produced using pandoc. The contents of the reference ODT
are ignored, but its stylesheets are used in the new ODT. If no
reference ODT is specified on the command line, pandoc will look
for `$HOME/.pandoc/reference.odt` (on unix) or
`C:\Documents And Settings\USERNAME\Application Data\pandoc\reference.odt`
(on Windows). If this is not found either, sensible defaults will be
for a file `reference.odt` in the user data directory (see
`--data-dir`). If this is not found either, sensible defaults will be
used.
-D *FORMAT*, \--print-default-template=*FORMAT*
@ -219,6 +218,20 @@ to Pandoc. Or use `html2markdown`(1), a wrapper around `pandoc`.
-T *STRING*, \--title-prefix=*STRING*
: Specify *STRING* as a prefix to the HTML window title.
\--data-dir*=DIRECTORY*
: Specify the user data directory to search for pandoc data files.
If this option is not specified, the default user data directory
will be used:
$HOME/.pandoc
in unix and
C:\Documents And Settings\USERNAME\Application Data\pandoc
in Windows. A reference ODT, `templates` directory, `s5` directory
placed in this directory will override pandoc's normal defaults.
\--dump-args
: Print information about command-line arguments to *stdout*, then exit.
The first line of output contains the name of the output file specified
@ -256,10 +269,8 @@ document. To see the default template that is used, just type
where `FORMAT` is the name of the output format. A custom template
can be specified using the `--template` option. You can also override
the system default templates for a given output format `FORMAT`
by putting a file `FORMAT.template` in `$HOME/.pandoc/templates`
(on unix) or
`C:\Documents And Settings\USERNAME\Application Data\pandoc\templates`
(on Windows).
by putting a file `templates/FORMAT.template` in the user data
directory (see `--data-dir`, below).
Templates may contain *variables*. Variable names are sequences of
alphanumerics, `-`, and `_`, starting with a letter. A variable name

View file

@ -5,9 +5,9 @@ import System.FilePath ( (</>) )
import Text.Pandoc.Shared (readDataFile)
-- | String containing LaTeXMathML javascript.
latexMathMLScript :: IO String
latexMathMLScript = do
jsCom <- readDataFile $ "data" </> "LaTeXMathML.js.comment"
jsPacked <- readDataFile $ "data" </> "LaTeXMathML.js.packed"
latexMathMLScript :: FilePath -> IO String
latexMathMLScript datadir = do
jsCom <- readDataFile datadir $ "data" </> "LaTeXMathML.js.comment"
jsPacked <- readDataFile datadir $ "data" </> "LaTeXMathML.js.packed"
return $ "<script type=\"text/javascript\">\n" ++ jsCom ++ jsPacked ++
"</script>\n"

View file

@ -42,18 +42,18 @@ import System.Directory
import Control.Monad (liftM)
-- | Produce an ODT file from OpenDocument XML.
saveOpenDocumentAsODT :: FilePath -- ^ Pathname of ODT file to be produced.
saveOpenDocumentAsODT :: FilePath -- ^ Path of user data directory
-> FilePath -- ^ Pathname of ODT file to be produced.
-> FilePath -- ^ Relative directory of source file.
-> Maybe FilePath -- ^ Path specified by --reference-odt
-> String -- ^ OpenDocument XML contents.
-> IO ()
saveOpenDocumentAsODT destinationODTPath sourceDirRelative mbRefOdt xml = do
saveOpenDocumentAsODT datadir destinationODTPath sourceDirRelative mbRefOdt xml = do
refArchive <- liftM toArchive $
case mbRefOdt of
Just f -> B.readFile f
Nothing -> do
userDataDir <- getAppUserDataDirectory "pandoc"
let userRefOdt = userDataDir </> "reference.odt"
let userRefOdt = datadir </> "reference.odt"
userRefOdtExists <- doesFileExist userRefOdt
if userRefOdtExists
then B.readFile userRefOdt

View file

@ -1044,9 +1044,9 @@ inDirectory path action = do
setCurrentDirectory oldDir
return result
-- | Read file from user data directory or, if not found there, from
-- Cabal data directory. On unix the user data directory is @$HOME/.pandoc@.
readDataFile :: FilePath -> IO String
readDataFile fname = do
userDir <- getAppUserDataDirectory "pandoc"
catch (readFile $ userDir </> fname) (\_ -> getDataFileName fname >>= readFile)
-- | Read file from specified user data directory or, if not found there, from
-- Cabal data directory.
readDataFile :: FilePath -> FilePath -> IO String
readDataFile userDir fname = catch
(readFile $ userDir </> fname)
(\_ -> getDataFileName fname >>= readFile)

View file

@ -66,8 +66,7 @@ You may optionally specify separators using @$sep$@:
module Text.Pandoc.Templates ( renderTemplate
, TemplateTarget
, getTemplate
, getDefaultTemplate) where
, getTemplate ) where
import Text.ParserCombinators.Parsec
import Control.Monad (liftM, when, forM)
@ -77,7 +76,7 @@ import Data.List (intercalate, intersperse)
import Text.PrettyPrint (text, Doc)
import Text.XHtml (primHtml, Html)
import Data.ByteString.Lazy.UTF8 (ByteString, fromString)
import System.Directory
import Text.Pandoc.Shared (readDataFile)
-- Note: ghc >= 6.12 (base >=4.2) supports unicode through iconv
-- So we use System.IO.UTF8 only if we have an earlier version
#if MIN_VERSION_base(4,2,0)
@ -88,25 +87,18 @@ import System.IO.UTF8 ( readFile )
import Paths_pandoc (getDataFileName)
-- | Get a template for the specified writer.
getTemplate :: Bool -- ^ Allow override from user's application data directory?
-> String -- ^ Name of writer
getTemplate :: (Maybe FilePath) -- ^ User data directory to search first
-> String -- ^ Name of writer
-> IO (Either E.IOException String)
getTemplate _ "native" = return $ Right ""
getTemplate user "s5" = getTemplate user "html"
getTemplate user "odt" = getTemplate user "opendocument"
getTemplate user writer = do
let format = takeWhile (/='+') writer -- strip off "+lhs" if present
userDir <- getAppUserDataDirectory "pandoc"
let fname = "templates" </> format <.> "template"
hasUserTemplate <- doesFileExist (userDir </> fname)
E.try $ if user && hasUserTemplate
then readFile $ userDir </> fname
else getDataFileName fname >>= readFile
-- | Get the default template, either from the application's user data
-- directory (~/.pandoc on unix) or from the cabal data directory.
getDefaultTemplate :: String -> IO (Either E.IOException String)
getDefaultTemplate = getTemplate True
E.try $ case user of
Just d -> readDataFile d fname
Nothing -> getDataFileName fname >>= readFile
data TemplateState = TemplateState Int [(String,String)]

View file

@ -44,30 +44,30 @@ import Text.XHtml.Strict
import System.FilePath ( (</>) )
import Data.List ( intercalate )
s5HeaderIncludes :: IO String
s5HeaderIncludes = do
c <- s5CSS
j <- s5Javascript
s5HeaderIncludes :: FilePath -> IO String
s5HeaderIncludes datadir = do
c <- s5CSS datadir
j <- s5Javascript datadir
return $ s5Meta ++ c ++ j
s5Meta :: String
s5Meta = "<!-- configuration parameters -->\n<meta name=\"defaultView\" content=\"slideshow\" />\n<meta name=\"controlVis\" content=\"hidden\" />\n"
s5Javascript :: IO String
s5Javascript = do
jsCom <- readDataFile $ "s5" </> "default" </> "slides.js.comment"
jsPacked <- readDataFile $ "s5" </> "default" </> "slides.js.packed"
s5Javascript :: FilePath -> IO String
s5Javascript datadir = do
jsCom <- readDataFile datadir $ "s5" </> "default" </> "slides.js.comment"
jsPacked <- readDataFile datadir $ "s5" </> "default" </> "slides.js.packed"
return $ "<script type=\"text/javascript\">\n" ++ jsCom ++ jsPacked ++
"</script>\n"
s5CSS :: IO String
s5CSS = do
s5CoreCSS <- readDataFile $ "s5" </> "default" </> "s5-core.css"
s5FramingCSS <- readDataFile $ "s5" </> "default" </> "framing.css"
s5PrettyCSS <- readDataFile $ "s5" </> "default" </> "pretty.css"
s5OperaCSS <- readDataFile $ "s5" </> "default" </> "opera.css"
s5OutlineCSS <- readDataFile $ "s5" </> "default" </> "outline.css"
s5PrintCSS <- readDataFile $ "s5" </> "default" </> "print.css"
s5CSS :: FilePath -> IO String
s5CSS datadir = do
s5CoreCSS <- readDataFile datadir $ "s5" </> "default" </> "s5-core.css"
s5FramingCSS <- readDataFile datadir $ "s5" </> "default" </> "framing.css"
s5PrettyCSS <- readDataFile datadir $ "s5" </> "default" </> "pretty.css"
s5OperaCSS <- readDataFile datadir $ "s5" </> "default" </> "opera.css"
s5OutlineCSS <- readDataFile datadir $ "s5" </> "default" </> "outline.css"
s5PrintCSS <- readDataFile datadir $ "s5" </> "default" </> "print.css"
return $ "<style type=\"text/css\" media=\"projection\" id=\"slideProj\">\n" ++ s5CoreCSS ++ "\n" ++ s5FramingCSS ++ "\n" ++ s5PrettyCSS ++ "\n</style>\n<style type=\"text/css\" media=\"projection\" id=\"operaFix\">\n" ++ s5OperaCSS ++ "\n</style>\n<style type=\"text/css\" media=\"screen\" id=\"outlineStyle\">\n" ++ s5OutlineCSS ++ "\n</style>\n<style type=\"text/css\" media=\"print\" id=\"slidePrint\">\n" ++ s5PrintCSS ++ "\n</style>\n"
s5Links :: String

View file

@ -44,6 +44,7 @@ import System.Console.GetOpt
import Data.Maybe ( fromMaybe )
import Data.Char ( toLower )
import Data.List ( intercalate, isSuffixOf )
import System.Directory ( getAppUserDataDirectory )
import System.IO ( stdout, stderr )
-- Note: ghc >= 6.12 (base >=4.2) supports unicode through iconv
-- So we use System.IO.UTF8 only if we have an earlier version
@ -162,6 +163,7 @@ data Opt = Opt
, optEmailObfuscation :: ObfuscationMethod
, optIdentifierPrefix :: String
, optIndentedCodeClasses :: [String] -- ^ Default classes for indented code blocks
, optDataDir :: Maybe FilePath
#ifdef _CITEPROC
, optBiblioFile :: String
, optBiblioFormat :: String
@ -200,6 +202,7 @@ defaultOpts = Opt
, optEmailObfuscation = JavascriptObfuscation
, optIdentifierPrefix = ""
, optIndentedCodeClasses = []
, optDataDir = Nothing
#ifdef _CITEPROC
, optBiblioFile = []
, optBiblioFormat = []
@ -438,7 +441,7 @@ options =
, Option "D" ["print-default-template"]
(ReqArg
(\arg _ -> do
templ <- getDefaultTemplate arg
templ <- getTemplate Nothing arg
case templ of
Right t -> hPutStr stdout t
Left e -> error $ show e
@ -462,6 +465,12 @@ options =
"FILENAME")
""
#endif
, Option "" ["data-dir"]
(ReqArg
(\arg opt -> return opt { optDataDir = Just arg })
"DIRECTORY") -- "Directory containing pandoc data files."
""
, Option "" ["dump-args"]
(NoArg
(\opt -> return opt { optDumpArgs = True }))
@ -598,6 +607,7 @@ main = do
, optEmailObfuscation = obfuscationMethod
, optIdentifierPrefix = idPrefix
, optIndentedCodeClasses = codeBlockClasses
, optDataDir = mbDataDir
#ifdef _CITEPROC
, optBiblioFile = biblioFile
, optBiblioFormat = biblioFormat
@ -619,6 +629,10 @@ main = do
let sources = if ignoreArgs then [] else args
datadir <- case mbDataDir of
Just d -> return d
Nothing -> getAppUserDataDirectory "pandoc"
-- assign reader and writer based on options and filenames
let readerName' = if null readerName
then defaultReaderName sources
@ -636,7 +650,7 @@ main = do
Just r -> return r
Nothing -> error ("Unknown writer: " ++ writerName')
templ <- getDefaultTemplate writerName'
templ <- getTemplate (Just datadir) writerName'
let defaultTemplate = case templ of
Right t -> t
Left e -> error (show e)
@ -654,13 +668,13 @@ main = do
variables' <- if writerName' == "s5" && standalone'
then do
inc <- s5HeaderIncludes
inc <- s5HeaderIncludes datadir
return $ ("header-includes", inc) : variables
else return variables
variables'' <- case mathMethod of
LaTeXMathML Nothing -> do
s <- latexMathMLScript
s <- latexMathMLScript datadir
return $ ("latexmathml-script", s) : variables'
_ -> return variables'
@ -731,9 +745,9 @@ main = do
#endif
let writerOutput = writer writerOptions doc' ++ "\n"
case writerName' of
"odt" -> saveOpenDocumentAsODT outputFile sourceDirRelative referenceODT writerOutput
"odt" -> saveOpenDocumentAsODT datadir outputFile sourceDirRelative referenceODT writerOutput
_ -> if outputFile == "-"
then putStr writerOutput
else writeFile outputFile writerOutput