Man writer: give more fine-grained control in template.
Now the `title`, `section`, `header`, and `footer` can all be set individually in metadata. The `description` variable has been removed. Quotes have been added so that spaces are allowed in the title. If you have a title that begins COMMAND(1) footer here | header here pandoc will parse it as before into a title, section, header, and footer. But you can also specify these elements explicitly. Closes #885.
This commit is contained in:
parent
82e46bf385
commit
dd96213c05
4 changed files with 24 additions and 12 deletions
6
README
6
README
|
@ -793,6 +793,12 @@ depending on the output format, but include:
|
||||||
: color for citation links in LaTeX documents
|
: color for citation links in LaTeX documents
|
||||||
`links-as-notes`
|
`links-as-notes`
|
||||||
: causes links to be printed as footnotes in LaTeX documents
|
: causes links to be printed as footnotes in LaTeX documents
|
||||||
|
`section`
|
||||||
|
: section number in man pages
|
||||||
|
`header`
|
||||||
|
: header in man pages
|
||||||
|
`footer`
|
||||||
|
: footer in man pages
|
||||||
|
|
||||||
Variables may be set at the command line using the `-V/--variable`
|
Variables may be set at the command line using the `-V/--variable`
|
||||||
option. This allows users to include custom variables in their
|
option. This allows users to include custom variables in their
|
||||||
|
|
|
@ -1 +1 @@
|
||||||
Subproject commit 050ea0fa8dc51d1e722f8e88b7ce9a792474082f
|
Subproject commit 0d246e8af51f5a07f8460e790bcbd926d421c829
|
|
@ -39,6 +39,7 @@ import Data.List ( isPrefixOf, intersperse, intercalate )
|
||||||
import Text.Pandoc.Pretty
|
import Text.Pandoc.Pretty
|
||||||
import Text.Pandoc.Builder (deleteMeta)
|
import Text.Pandoc.Builder (deleteMeta)
|
||||||
import Control.Monad.State
|
import Control.Monad.State
|
||||||
|
import Data.Char ( isDigit )
|
||||||
|
|
||||||
type Notes = [[Block]]
|
type Notes = [[Block]]
|
||||||
data WriterState = WriterState { stNotes :: Notes
|
data WriterState = WriterState { stNotes :: Notes
|
||||||
|
@ -56,13 +57,20 @@ pandocToMan opts (Pandoc meta blocks) = do
|
||||||
else Nothing
|
else Nothing
|
||||||
let render' = render colwidth
|
let render' = render colwidth
|
||||||
titleText <- inlineListToMan opts $ docTitle meta
|
titleText <- inlineListToMan opts $ docTitle meta
|
||||||
let (cmdName, rest) = break (== ' ') $ render' titleText
|
let title' = render' titleText
|
||||||
let (title', section) = case reverse cmdName of
|
let setFieldsFromTitle =
|
||||||
(')':d:'(':xs) | d `elem` ['0'..'9'] ->
|
case break (== ' ') title' of
|
||||||
(reverse xs, [d])
|
(cmdName, rest) -> case reverse cmdName of
|
||||||
xs -> (reverse xs, "\"\"")
|
(')':d:'(':xs) | isDigit d ->
|
||||||
let description = hsep $
|
setField "title" (reverse xs) .
|
||||||
map (doubleQuotes . text . trim) $ splitBy (== '|') rest
|
setField "section" [d] .
|
||||||
|
case splitBy (=='|') rest of
|
||||||
|
(ft:hds) ->
|
||||||
|
setField "footer" (trim ft) .
|
||||||
|
setField "header"
|
||||||
|
(trim $ concat hds)
|
||||||
|
[] -> id
|
||||||
|
_ -> setField "title" title'
|
||||||
metadata <- metaToJSON
|
metadata <- metaToJSON
|
||||||
(fmap (render colwidth) . blockListToMan opts)
|
(fmap (render colwidth) . blockListToMan opts)
|
||||||
(fmap (render colwidth) . inlineListToMan opts)
|
(fmap (render colwidth) . inlineListToMan opts)
|
||||||
|
@ -73,9 +81,7 @@ pandocToMan opts (Pandoc meta blocks) = do
|
||||||
let main = render' $ body $$ notes' $$ text ""
|
let main = render' $ body $$ notes' $$ text ""
|
||||||
hasTables <- liftM stHasTables get
|
hasTables <- liftM stHasTables get
|
||||||
let context = setField "body" main
|
let context = setField "body" main
|
||||||
$ setField "title" title'
|
$ setFieldsFromTitle
|
||||||
$ setField "section" section
|
|
||||||
$ setField "description" (render' description)
|
|
||||||
$ setField "has-tables" hasTables
|
$ setField "has-tables" hasTables
|
||||||
$ foldl (\acc (x,y) -> setField x y acc)
|
$ foldl (\acc (x,y) -> setField x y acc)
|
||||||
metadata (writerVariables opts)
|
metadata (writerVariables opts)
|
||||||
|
|
|
@ -1,4 +1,4 @@
|
||||||
.TH Pandoc "" "July 17, 2006" "Test Suite"
|
.TH "Pandoc Test Suite" "" "July 17, 2006" "" ""
|
||||||
.PP
|
.PP
|
||||||
This is a set of tests for pandoc.
|
This is a set of tests for pandoc.
|
||||||
Most of them are adapted from John Gruber's markdown test suite.
|
Most of them are adapted from John Gruber's markdown test suite.
|
||||||
|
|
Loading…
Reference in a new issue