Added --list-* options.
Added `--list-input-formats`, `--list-output-formats`, `--list-extensions`, `--list-highlight-languages`, `--list-highlight-styles`. Removed list of highlighting languages from `--version` output. Removed list of input and output formats from default `--help` output. Closes #3173.
This commit is contained in:
parent
3f93ca5bba
commit
273d90bc19
2 changed files with 91 additions and 29 deletions
29
MANUAL.txt
29
MANUAL.txt
|
@ -262,7 +262,8 @@ General options
|
||||||
`markdown-pipe_tables+hard_line_breaks` is pandoc's Markdown
|
`markdown-pipe_tables+hard_line_breaks` is pandoc's Markdown
|
||||||
without pipe tables and with hard line breaks. See [Pandoc's
|
without pipe tables and with hard line breaks. See [Pandoc's
|
||||||
Markdown], below, for a list of extensions and
|
Markdown], below, for a list of extensions and
|
||||||
their names.
|
their names. See `--list-input-formats` and `--list-extensions`,
|
||||||
|
below.
|
||||||
|
|
||||||
`-t` *FORMAT*, `-w` *FORMAT*, `--to=`*FORMAT*, `--write=`*FORMAT*
|
`-t` *FORMAT*, `-w` *FORMAT*, `--to=`*FORMAT*, `--write=`*FORMAT*
|
||||||
|
|
||||||
|
@ -297,6 +298,7 @@ General options
|
||||||
below. Markdown syntax extensions can be individually
|
below. Markdown syntax extensions can be individually
|
||||||
enabled or disabled by appending `+EXTENSION` or
|
enabled or disabled by appending `+EXTENSION` or
|
||||||
`-EXTENSION` to the format name, as described above under `-f`.
|
`-EXTENSION` to the format name, as described above under `-f`.
|
||||||
|
See `--list-output-formats` and `--list-extensions`, below.
|
||||||
|
|
||||||
`-o` *FILE*, `--output=`*FILE*
|
`-o` *FILE*, `--output=`*FILE*
|
||||||
|
|
||||||
|
@ -338,6 +340,30 @@ General options
|
||||||
: Give verbose debugging output. Currently this only has an effect
|
: Give verbose debugging output. Currently this only has an effect
|
||||||
with PDF output.
|
with PDF output.
|
||||||
|
|
||||||
|
`--list-input-formats`
|
||||||
|
|
||||||
|
: List supported input formats, one per line.
|
||||||
|
|
||||||
|
`--list-output-formats`
|
||||||
|
|
||||||
|
: List supported output formats, one per line.
|
||||||
|
|
||||||
|
`--list-extensions`
|
||||||
|
|
||||||
|
: List supported Markdown extensions, one per line, followed
|
||||||
|
by a `+` or `-` indicating whether it is enabled by default
|
||||||
|
in pandoc's Markdown.
|
||||||
|
|
||||||
|
`--list-highlight-languages`
|
||||||
|
|
||||||
|
: List supported languages for syntax highlighting, one per
|
||||||
|
line.
|
||||||
|
|
||||||
|
`--list-highlight-styles`
|
||||||
|
|
||||||
|
: List supported styles for syntax highlighting, one per line.
|
||||||
|
See `--highlight-style`.
|
||||||
|
|
||||||
`-v`, `--version`
|
`-v`, `--version`
|
||||||
|
|
||||||
: Print version.
|
: Print version.
|
||||||
|
@ -583,6 +609,7 @@ General writer options
|
||||||
Options are `pygments` (the default), `kate`, `monochrome`,
|
Options are `pygments` (the default), `kate`, `monochrome`,
|
||||||
`espresso`, `zenburn`, `haddock`, and `tango`. For more information
|
`espresso`, `zenburn`, `haddock`, and `tango`. For more information
|
||||||
on syntax highlighting in pandoc, see [Syntax highlighting], below.
|
on syntax highlighting in pandoc, see [Syntax highlighting], below.
|
||||||
|
See also `--list-highlight-styles`.
|
||||||
|
|
||||||
`-H` *FILE*, `--include-in-header=`*FILE*
|
`-H` *FILE*, `--include-in-header=`*FILE*
|
||||||
|
|
||||||
|
|
91
pandoc.hs
91
pandoc.hs
|
@ -48,8 +48,9 @@ import System.Environment ( getArgs, getProgName )
|
||||||
import System.Exit ( ExitCode (..), exitSuccess )
|
import System.Exit ( ExitCode (..), exitSuccess )
|
||||||
import System.FilePath
|
import System.FilePath
|
||||||
import System.Console.GetOpt
|
import System.Console.GetOpt
|
||||||
|
import qualified Data.Set as Set
|
||||||
import Data.Char ( toLower, toUpper )
|
import Data.Char ( toLower, toUpper )
|
||||||
import Data.List ( delete, intercalate, isPrefixOf, isSuffixOf, sort )
|
import Data.List ( intercalate, isPrefixOf, isSuffixOf, sort )
|
||||||
import System.Directory ( getAppUserDataDirectory, findExecutable,
|
import System.Directory ( getAppUserDataDirectory, findExecutable,
|
||||||
doesFileExist, Permissions(..), getPermissions )
|
doesFileExist, Permissions(..), getPermissions )
|
||||||
import System.IO ( stdout, stderr )
|
import System.IO ( stdout, stderr )
|
||||||
|
@ -88,10 +89,7 @@ copyrightMessage = intercalate "\n" [
|
||||||
compileInfo :: String
|
compileInfo :: String
|
||||||
compileInfo =
|
compileInfo =
|
||||||
"\nCompiled with texmath " ++
|
"\nCompiled with texmath " ++
|
||||||
VERSION_texmath ++ ", highlighting-kate " ++ VERSION_highlighting_kate ++
|
VERSION_texmath ++ ", highlighting-kate " ++ VERSION_highlighting_kate
|
||||||
".\nSyntax highlighting is supported for the following languages:\n " ++
|
|
||||||
wrapWords 4 78
|
|
||||||
[map toLower l | l <- languages, l /= "Alert" && l /= "Alert_indent"]
|
|
||||||
|
|
||||||
-- | Converts a list of strings into a single string with the items printed as
|
-- | Converts a list of strings into a single string with the items printed as
|
||||||
-- comma separated words in lines with a maximum line length.
|
-- comma separated words in lines with a maximum line length.
|
||||||
|
@ -158,6 +156,16 @@ externalFilter f args' d = do
|
||||||
filterException e = err 83 $ "Error running filter " ++ f ++ "\n" ++
|
filterException e = err 83 $ "Error running filter " ++ f ++ "\n" ++
|
||||||
show e
|
show e
|
||||||
|
|
||||||
|
highlightingStyles :: [(String, Style)]
|
||||||
|
highlightingStyles =
|
||||||
|
[("pygments", pygments),
|
||||||
|
("tango", tango),
|
||||||
|
("espresso", espresso),
|
||||||
|
("zenburn", zenburn),
|
||||||
|
("kate", kate),
|
||||||
|
("monochrome", monochrome),
|
||||||
|
("haddock", haddock)]
|
||||||
|
|
||||||
-- | Data structure for command line options.
|
-- | Data structure for command line options.
|
||||||
data Opt = Opt
|
data Opt = Opt
|
||||||
{ optTabStop :: Int -- ^ Number of spaces per tab
|
{ optTabStop :: Int -- ^ Number of spaces per tab
|
||||||
|
@ -517,17 +525,9 @@ options =
|
||||||
, Option "" ["highlight-style"]
|
, Option "" ["highlight-style"]
|
||||||
(ReqArg
|
(ReqArg
|
||||||
(\arg opt -> do
|
(\arg opt -> do
|
||||||
newStyle <- case map toLower arg of
|
case lookup (map toLower arg) highlightingStyles of
|
||||||
"pygments" -> return pygments
|
Just s -> return opt{ optHighlightStyle = s }
|
||||||
"tango" -> return tango
|
Nothing -> err 39 $ "Unknown style: " ++ arg)
|
||||||
"espresso" -> return espresso
|
|
||||||
"zenburn" -> return zenburn
|
|
||||||
"kate" -> return kate
|
|
||||||
"monochrome" -> return monochrome
|
|
||||||
"haddock" -> return haddock
|
|
||||||
_ -> err 39 $
|
|
||||||
"Unknown style :" ++ arg
|
|
||||||
return opt{ optHighlightStyle = newStyle })
|
|
||||||
"STYLE")
|
"STYLE")
|
||||||
"" -- "Style for highlighted code"
|
"" -- "Style for highlighted code"
|
||||||
|
|
||||||
|
@ -918,11 +918,56 @@ options =
|
||||||
let allopts = unwords (concatMap optnames options)
|
let allopts = unwords (concatMap optnames options)
|
||||||
UTF8.hPutStrLn stdout $ printf tpl allopts
|
UTF8.hPutStrLn stdout $ printf tpl allopts
|
||||||
(unwords (map fst readers))
|
(unwords (map fst readers))
|
||||||
(unwords ("pdf": map fst writers))
|
(unwords (map fst writers))
|
||||||
ddir
|
ddir
|
||||||
exitSuccess ))
|
exitSuccess ))
|
||||||
"" -- "Print bash completion script"
|
"" -- "Print bash completion script"
|
||||||
|
|
||||||
|
, Option "" ["list-input-formats"]
|
||||||
|
(NoArg
|
||||||
|
(\_ -> do
|
||||||
|
let readers'names = sort (map fst readers)
|
||||||
|
mapM_ (UTF8.hPutStrLn stdout) readers'names
|
||||||
|
exitSuccess ))
|
||||||
|
""
|
||||||
|
|
||||||
|
, Option "" ["list-output-formats"]
|
||||||
|
(NoArg
|
||||||
|
(\_ -> do
|
||||||
|
let writers'names = sort (map fst writers)
|
||||||
|
mapM_ (UTF8.hPutStrLn stdout) writers'names
|
||||||
|
exitSuccess ))
|
||||||
|
""
|
||||||
|
|
||||||
|
, Option "" ["list-extensions"]
|
||||||
|
(NoArg
|
||||||
|
(\_ -> do
|
||||||
|
let showExt x = drop 4 (show x) ++
|
||||||
|
if x `Set.member` pandocExtensions
|
||||||
|
then " +"
|
||||||
|
else " -"
|
||||||
|
mapM_ (UTF8.hPutStrLn stdout . showExt)
|
||||||
|
([minBound..maxBound] :: [Extension])
|
||||||
|
exitSuccess ))
|
||||||
|
""
|
||||||
|
|
||||||
|
, Option "" ["list-highlight-languages"]
|
||||||
|
(NoArg
|
||||||
|
(\_ -> do
|
||||||
|
let langs = [map toLower l | l <- languages,
|
||||||
|
l /= "Alert" && l /= "Alert_indent"]
|
||||||
|
mapM_ (UTF8.hPutStrLn stdout) langs
|
||||||
|
exitSuccess ))
|
||||||
|
""
|
||||||
|
|
||||||
|
, Option "" ["list-highlight-styles"]
|
||||||
|
(NoArg
|
||||||
|
(\_ -> do
|
||||||
|
mapM_ (UTF8.hPutStrLn stdout) $
|
||||||
|
map fst highlightingStyles
|
||||||
|
exitSuccess ))
|
||||||
|
""
|
||||||
|
|
||||||
, Option "v" ["version"]
|
, Option "v" ["version"]
|
||||||
(NoArg
|
(NoArg
|
||||||
(\_ -> do
|
(\_ -> do
|
||||||
|
@ -961,17 +1006,7 @@ readMetaValue s = case decode (UTF8.fromString s) of
|
||||||
|
|
||||||
-- Returns usage message
|
-- Returns usage message
|
||||||
usageMessage :: String -> [OptDescr (Opt -> IO Opt)] -> String
|
usageMessage :: String -> [OptDescr (Opt -> IO Opt)] -> String
|
||||||
usageMessage programName = usageInfo
|
usageMessage programName = usageInfo (programName ++ " [OPTIONS] [FILES]")
|
||||||
(programName ++ " [OPTIONS] [FILES]" ++ "\nInput formats: " ++
|
|
||||||
wrapWords 16 78 readers'names ++
|
|
||||||
'\n' : replicate 16 ' ' ++
|
|
||||||
"[* only Pandoc's JSON version of native AST]" ++ "\nOutput formats: " ++
|
|
||||||
wrapWords 16 78 writers'names ++
|
|
||||||
'\n' : replicate 16 ' ' ++
|
|
||||||
"[** for pdf output, use latex or beamer and -o FILENAME.pdf]\nOptions:")
|
|
||||||
where
|
|
||||||
writers'names = sort $ "json*" : "pdf**" : delete "json" (map fst writers)
|
|
||||||
readers'names = sort $ "json*" : delete "json" (map fst readers)
|
|
||||||
|
|
||||||
-- Determine default reader based on source file extensions
|
-- Determine default reader based on source file extensions
|
||||||
defaultReaderName :: String -> [FilePath] -> String
|
defaultReaderName :: String -> [FilePath] -> String
|
||||||
|
|
Loading…
Add table
Reference in a new issue