Man writer: updated to use Pretty.

This commit is contained in:
John MacFarlane 2010-12-22 00:21:56 -08:00
parent c904024944
commit fd07db16e9
3 changed files with 42 additions and 46 deletions

View file

@ -35,7 +35,7 @@ import Text.Pandoc.Shared
import Text.Pandoc.Readers.TeXMath import Text.Pandoc.Readers.TeXMath
import Text.Printf ( printf ) import Text.Printf ( printf )
import Data.List ( isPrefixOf, intersperse, intercalate ) import Data.List ( isPrefixOf, intersperse, intercalate )
import Text.PrettyPrint.HughesPJ hiding ( Str ) import Text.Pandoc.Pretty
import Control.Monad.State import Control.Monad.State
type Notes = [[Block]] type Notes = [[Block]]
@ -52,27 +52,31 @@ pandocToMan opts (Pandoc (Meta title authors date) blocks) = do
titleText <- inlineListToMan opts title titleText <- inlineListToMan opts title
authors' <- mapM (inlineListToMan opts) authors authors' <- mapM (inlineListToMan opts) authors
date' <- inlineListToMan opts date date' <- inlineListToMan opts date
let (cmdName, rest) = break (== ' ') $ render titleText let colwidth = if writerWrapText opts
then Just $ writerColumns opts
else Nothing
let render' = render colwidth
let (cmdName, rest) = break (== ' ') $ render' titleText
let (title', section) = case reverse cmdName of let (title', section) = case reverse cmdName of
(')':d:'(':xs) | d `elem` ['0'..'9'] -> (')':d:'(':xs) | d `elem` ['0'..'9'] ->
(text (reverse xs), char d) (text (reverse xs), char d)
xs -> (text (reverse xs), doubleQuotes empty) xs -> (text (reverse xs), doubleQuotes empty)
let description = hsep $ let description = hsep $
map (doubleQuotes . text . removeLeadingTrailingSpace) $ map (doubleQuotes . text . removeLeadingTrailingSpace) $
splitBy (== '|') rest splitBy (== '|') rest
body <- blockListToMan opts blocks body <- blockListToMan opts blocks
notes <- liftM stNotes get notes <- liftM stNotes get
notes' <- notesToMan opts (reverse notes) notes' <- notesToMan opts (reverse notes)
let main = render $ body $$ notes' $$ text "" let main = render' $ body $$ notes' $$ text ""
hasTables <- liftM stHasTables get hasTables <- liftM stHasTables get
let context = writerVariables opts ++ let context = writerVariables opts ++
[ ("body", main) [ ("body", main)
, ("title", render title') , ("title", render' title')
, ("section", render section) , ("section", render' section)
, ("date", render date') , ("date", render' date')
, ("description", render description) ] ++ , ("description", render' description) ] ++
[ ("has-tables", "yes") | hasTables ] ++ [ ("has-tables", "yes") | hasTables ] ++
[ ("author", render a) | a <- authors' ] [ ("author", render' a) | a <- authors' ]
if writerStandalone opts if writerStandalone opts
then return $ renderTemplate context $ writerTemplate opts then return $ renderTemplate context $ writerTemplate opts
else return main else return main
@ -89,7 +93,7 @@ notesToMan opts notes =
noteToMan :: WriterOptions -> Int -> [Block] -> State WriterState Doc noteToMan :: WriterOptions -> Int -> [Block] -> State WriterState Doc
noteToMan opts num note = do noteToMan opts num note = do
contents <- blockListToMan opts note contents <- blockListToMan opts note
let marker = text "\n.SS [" <> text (show num) <> char ']' let marker = cr <> text ".SS " <> brackets (text (show num))
return $ marker $$ contents return $ marker $$ contents
-- | Association list of characters to escape. -- | Association list of characters to escape.
@ -136,14 +140,13 @@ blockToMan :: WriterOptions -- ^ Options
-> State WriterState Doc -> State WriterState Doc
blockToMan _ Null = return empty blockToMan _ Null = return empty
blockToMan opts (Plain inlines) = blockToMan opts (Plain inlines) =
liftM vcat $ mapM (wrapIfNeeded opts (inlineListToMan opts)) $ liftM vcat $ mapM (inlineListToMan opts) $ splitSentences inlines
splitSentences inlines
blockToMan opts (Para inlines) = do blockToMan opts (Para inlines) = do
contents <- liftM vcat $ mapM (wrapIfNeeded opts (inlineListToMan opts)) $ contents <- liftM vcat $ mapM (inlineListToMan opts) $
splitSentences inlines splitSentences inlines
return $ text ".PP" $$ contents return $ text ".PP" $$ contents
blockToMan _ (RawHtml _) = return empty blockToMan _ (RawHtml _) = return empty
blockToMan _ HorizontalRule = return $ text $ ".PP\n * * * * *" blockToMan _ HorizontalRule = return $ text ".PP" $$ text " * * * * *"
blockToMan opts (Header level inlines) = do blockToMan opts (Header level inlines) = do
contents <- inlineListToMan opts inlines contents <- inlineListToMan opts inlines
let heading = case level of let heading = case level of
@ -256,7 +259,7 @@ definitionListItemToMan opts (label, defs) = do
mapM (\item -> blockToMan opts item) rest mapM (\item -> blockToMan opts item) rest
first' <- blockToMan opts first first' <- blockToMan opts first
return $ first' $$ text ".RS" $$ rest' $$ text ".RE" return $ first' $$ text ".RS" $$ rest' $$ text ".RE"
return $ text ".TP\n.B " <> labelText $+$ contents return $ text ".TP" $$ text ".B " <> labelText $$ contents
-- | Convert list of Pandoc block elements to man. -- | Convert list of Pandoc block elements to man.
blockListToMan :: WriterOptions -- ^ Options blockListToMan :: WriterOptions -- ^ Options
@ -309,11 +312,12 @@ inlineToMan _ (Str str) = return $ text $ escapeString str
inlineToMan opts (Math InlineMath str) = inlineListToMan opts $ readTeXMath str inlineToMan opts (Math InlineMath str) = inlineListToMan opts $ readTeXMath str
inlineToMan opts (Math DisplayMath str) = do inlineToMan opts (Math DisplayMath str) = do
contents <- inlineListToMan opts $ readTeXMath str contents <- inlineListToMan opts $ readTeXMath str
return $ text ".RS" $$ contents $$ text ".RE" return $ cr <> text ".RS" $$ contents $$ text ".RE"
inlineToMan _ (TeX _) = return empty inlineToMan _ (TeX _) = return empty
inlineToMan _ (HtmlInline _) = return empty inlineToMan _ (HtmlInline _) = return empty
inlineToMan _ (LineBreak) = return $ text "\n.PD 0\n.P\n.PD\n" inlineToMan _ (LineBreak) = return $
inlineToMan _ Space = return $ char ' ' cr <> text ".PD 0" $$ text ".P" $$ text ".PD" <> cr
inlineToMan _ Space = return space
inlineToMan opts (Link txt (src, _)) = do inlineToMan opts (Link txt (src, _)) = do
linktext <- inlineListToMan opts txt linktext <- inlineListToMan opts txt
let srcSuffix = if isPrefixOf "mailto:" src then drop 7 src else src let srcSuffix = if isPrefixOf "mailto:" src then drop 7 src else src

View file

@ -264,4 +264,4 @@ T}@T{
Here\[aq]s another one. Here\[aq]s another one.
Note the blank line between rows. Note the blank line between rows.
T} T}
.TE .TE

View file

@ -26,8 +26,8 @@ Here's a regular paragraph.
In Markdown 1.0.0 and earlier. In Markdown 1.0.0 and earlier.
Version 8. Version 8.
This line turns into a list item. This line turns into a list item.
Because a hard-wrapped line in the middle of a paragraph looked Because a hard-wrapped line in the middle of a paragraph looked like a list
like a list item. item.
.PP .PP
Here's one with a bullet. Here's one with a bullet.
* criminey. * criminey.
@ -531,8 +531,8 @@ Superscripts: a^bc^d a^\f[I]hello\f[]^ a^hello\ there^.
.PP .PP
Subscripts: H~2~O, H~23~O, H~many\ of\ them~O. Subscripts: H~2~O, H~23~O, H~many\ of\ them~O.
.PP .PP
These should not be superscripts or subscripts, because of the These should not be superscripts or subscripts, because of the unescaped
unescaped spaces: a^b c^d, a~b c~d. spaces: a^b c^d, a~b c~d.
.PP .PP
* * * * * * * * * *
.SH Smart quotes, ellipses, dashes .SH Smart quotes, ellipses, dashes
@ -547,8 +547,8 @@ So is `pine.'
.PP .PP
`He said, \[lq]I want to go.\[rq]' Were you alive in the 70's? `He said, \[lq]I want to go.\[rq]' Were you alive in the 70's?
.PP .PP
Here is some quoted `\f[C]code\f[]' and a Here is some quoted `\f[C]code\f[]' and a \[lq]quoted
\[lq]quoted link (http://example.com/?foo=1&bar=2)\[rq]. link (http://example.com/?foo=1&bar=2)\[rq].
.PP .PP
Some dashes: one\[em]two \[em] three\[em]four \[em] five. Some dashes: one\[em]two \[em] three\[em]four \[em] five.
.PP .PP
@ -641,7 +641,7 @@ Greater-than: >
.PP .PP
Hash: # Hash: #
.PP .PP
Period: \&. Period: .
.PP .PP
Bang: ! Bang: !
.PP .PP
@ -701,11 +701,9 @@ Foo bar (/url/).
Foo biz (/url/). Foo biz (/url/).
.SS With ampersands .SS With ampersands
.PP .PP
Here's a Here's a link with an ampersand in the URL (http://example.com/?foo=1&bar=2).
link with an ampersand in the URL (http://example.com/?foo=1&bar=2).
.PP .PP
Here's a link with an amersand in the link text: Here's a link with an amersand in the link text: AT&T (http://att.com/).
AT&T (http://att.com/).
.PP .PP
Here's an inline link (/script?foo=1&bar=2). Here's an inline link (/script?foo=1&bar=2).
.PP .PP
@ -746,9 +744,9 @@ Here is a movie [IMAGE: movie (movie.jpg)] icon.
* * * * * * * * * *
.SH Footnotes .SH Footnotes
.PP .PP
Here is a footnote reference,[1] and another.[2] This should Here is a footnote reference,[1] and another.[2] This should \f[I]not\f[] be a
\f[I]not\f[] be a footnote reference, because it contains a footnote reference, because it contains a space.[^my note] Here is an inline
space.[^my note] Here is an inline note.[3] note.[3]
.RS .RS
.PP .PP
Notes can go in quotes.[4] Notes can go in quotes.[4]
@ -756,23 +754,20 @@ Notes can go in quotes.[4]
.IP "1." 3 .IP "1." 3
And in list items.[5] And in list items.[5]
.PP .PP
This paragraph should not be part of the note, as it is not This paragraph should not be part of the note, as it is not indented.
indented.
.SH NOTES .SH NOTES
.SS [1] .SS [1]
.PP .PP
Here is the footnote. Here is the footnote.
It can go anywhere after the footnote reference. It can go anywhere after the footnote reference.
It need not be placed at the end of the document. It need not be placed at the end of the document.
.SS [2] .SS [2]
.PP .PP
Here's the long note. Here's the long note.
This one contains multiple blocks. This one contains multiple blocks.
.PP .PP
Subsequent blocks are indented to show that they belong to the Subsequent blocks are indented to show that they belong to the footnote (as
footnote (as with list items). with list items).
.IP .IP
.nf .nf
\f[C] \f[C]
@ -780,19 +775,16 @@ footnote (as with list items).
\f[] \f[]
.fi .fi
.PP .PP
If you want, you can indent every line, but you can also be lazy If you want, you can indent every line, but you can also be lazy and just
and just indent the first line of each block. indent the first line of each block.
.SS [3] .SS [3]
.PP .PP
This is \f[I]easier\f[] to type. This is \f[I]easier\f[] to type.
Inline notes may contain links (http://google.com) and \f[C]]\f[] Inline notes may contain links (http://google.com) and \f[C]]\f[] verbatim
verbatim characters, as well as [bracketed text]. characters, as well as [bracketed text].
.SS [4] .SS [4]
.PP .PP
In quote. In quote.
.SS [5] .SS [5]
.PP .PP
In list. In list.