Changes to Texinfo writer:

+ No space between paragraph and following @verbatim (provides more
  pleasing appearance in text formats)
+ Blank line consistently after list environments.
+ Removed deVerb.
+ Use @code instead of @verb for inline code (this solves the character
  escaping problem for texi2dvi and texi2pdf).
+ Modified test suite accordingly.
+ Added Peter Wang to copyright statement (for Texinfo.hs).
+ Added news of Texinfo writer to README.
+ Added Texinfo to list of formats in man page, and removed extra 'groff'.
+ Updated macports with Texinfo format.
+ Updated FreeBSD pkg-descr with Texinfo format.
+ Updated web page with Texinfo writer.
+ Added demos for Texinfo writer.
+ Added Texinfo to package description in debian/control.
+ Added texi & texinfo extensions to Main.hs, and fixed bug in determining
  default output extension.
+ Changed from texinfo to texi extension in web demo.


git-svn-id: https://pandoc.googlecode.com/svn/trunk@1244 788f1e2b-df1e-0410-8736-df70ead52e1b
This commit is contained in:
fiddlosopher 2008-02-24 05:48:59 +00:00
parent 49e0e507b7
commit 858269dd20
11 changed files with 124 additions and 101 deletions

38
Main.hs
View file

@ -373,24 +373,26 @@ defaultWriterName :: FilePath -> String
defaultWriterName "-" = "html" -- no output file
defaultWriterName x =
case takeExtension (map toLower x) of
"" -> "markdown" -- empty extension
"tex" -> "latex"
"latex" -> "latex"
"ltx" -> "latex"
"context" -> "context"
"ctx" -> "context"
"rtf" -> "rtf"
"rst" -> "rst"
"s5" -> "s5"
"native" -> "native"
"txt" -> "markdown"
"text" -> "markdown"
"md" -> "markdown"
"markdown" -> "markdown"
"db" -> "docbook"
"xml" -> "docbook"
"sgml" -> "docbook"
[x] | x `elem` ['1'..'9'] -> "man"
"" -> "markdown" -- empty extension
".tex" -> "latex"
".latex" -> "latex"
".ltx" -> "latex"
".context" -> "context"
".ctx" -> "context"
".rtf" -> "rtf"
".rst" -> "rst"
".s5" -> "s5"
".native" -> "native"
".txt" -> "markdown"
".text" -> "markdown"
".md" -> "markdown"
".markdown" -> "markdown"
".texi" -> "texinfo"
".texinfo" -> "texinfo"
".db" -> "docbook"
".xml" -> "docbook"
".sgml" -> "docbook"
['.',x] | x `elem` ['1'..'9'] -> "man"
_ -> "html"
main = do

30
README
View file

@ -6,9 +6,9 @@ Pandoc is a [Haskell] library for converting from one markup format to
another, and a command-line tool that uses this library. It can read
[markdown] and (subsets of) [reStructuredText], [HTML], and [LaTeX], and
it can write [markdown], [reStructuredText], [HTML], [LaTeX], [ConTeXt],
[RTF], [DocBook XML], [groff man] pages, and [S5] HTML slide shows.
Pandoc's version of markdown contains some enhancements, like footnotes
and embedded LaTeX.
[RTF], [DocBook XML], [GNU Texinfo], [groff man] pages, and [S5] HTML
slide shows. Pandoc's version of markdown contains some enhancements,
like footnotes and embedded LaTeX.
In contrast to existing tools for converting markdown to HTML, which
use regex substitutions, Pandoc has a modular design: it consists of a
@ -27,12 +27,14 @@ or output format requires only adding a reader or writer.
[DocBook XML]: http://www.docbook.org/
[groff man]: http://developer.apple.com/DOCUMENTATION/Darwin/Reference/ManPages/man7/groff_man.7.html
[Haskell]: http://www.haskell.org/
[GNU Texinfo]: http://www.gnu.org/software/texinfo/
© 2006-7 John MacFarlane (jgm at berkeley dot edu). Released under the
[GPL], version 2 or greater. This software carries no warranty of
any kind. (See COPYRIGHT for full copyright and warranty notices.)
Recai Oktaş (roktas at debian dot org) deserves credit for the build
system, the debian package, and the robust wrapper scripts.
Peter Wang deserves credit for the Texinfo writer.
[GPL]: http://www.gnu.org/copyleft/gpl.html "GNU General Public License"
@ -105,16 +107,16 @@ To convert `hello.html` from html to markdown:
Supported output formats include `markdown`, `latex`, `context`
(ConTeXt), `html`, `rtf` (rich text format), `rst` (reStructuredText),
`docbook` (DocBook XML), `man` (groff man), and `s5` (which produces an
HTML file that acts like powerpoint). Supported input formats include
`markdown`, `html`, `latex`, and `rst`. Note that the `rst` reader only
parses a subset of reStructuredText syntax. For example, it doesn't
handle tables, option lists, or footnotes. But for simple documents it
should be adequate. The `latex` and `html` readers are also limited in
what they can do. Because the `html` reader is picky about the HTML it
parses, it is recommended that you pipe HTML through [HTML Tidy] before
sending it to `pandoc`, or use the `html2markdown` script described
below.
`docbook` (DocBook XML), `texinfo`, `man` (groff man), and `s5` (which
produces an HTML file that acts like powerpoint). Supported input
formats include `markdown`, `html`, `latex`, and `rst`. Note that the
`rst` reader only parses a subset of reStructuredText syntax. For
example, it doesn't handle tables, option lists, or footnotes. But for
simple documents it should be adequate. The `latex` and `html` readers
are also limited in what they can do. Because the `html` reader is picky
about the HTML it parses, it is recommended that you pipe HTML through
[HTML Tidy] before sending it to `pandoc`, or use the `html2markdown`
script described below.
If you don't specify a reader or writer explicitly, `pandoc` will
try to determine the input and output format from the extensions of
@ -913,6 +915,8 @@ In reStructuredText output, it will be rendered using an interpreted
text role `:math:`, as described
[here](http://www.american.edu/econ/itex2mml/mathhack.rst).
In Texinfo output, it will be rendered inside a `@math` command.
In groff man output, it will be rendered verbatim without $'s.
In RTF and Docbook output, it will be rendered, as far as possible,

View file

@ -129,14 +129,6 @@ stringToTexinfo = escapeStringUsing texinfoEscapes
inCmd :: String -> Doc -> Doc
inCmd cmd contents = char '@' <> text cmd <> braces contents
-- | Remove all code elements from list of inline elements
-- (because it's illegal to have verbatim inside some command arguments)
-- XXX not sure about this
deVerb :: [Inline] -> [Inline]
deVerb [] = []
deVerb ((Code str):rest) = (Code $ stringToTexinfo str):(deVerb rest)
deVerb (other:rest) = other:(deVerb rest)
-- | Convert Pandoc block element to Texinfo.
blockToTexinfo :: Block -- ^ Block to convert
-> State WriterState Doc
@ -146,9 +138,8 @@ blockToTexinfo Null = return empty
blockToTexinfo (Plain lst) =
inlineListToTexinfo lst
blockToTexinfo (Para lst) = do
result <- inlineListToTexinfo lst
return $ result <> char '\n'
blockToTexinfo (Para lst) =
inlineListToTexinfo lst -- this is handled differently from Plain in blockListToTexinfo
blockToTexinfo (BlockQuote lst) = do
contents <- blockListToTexinfo lst
@ -157,9 +148,6 @@ blockToTexinfo (BlockQuote lst) = do
text "@end quotation"
blockToTexinfo (CodeBlock _ str) = do
-- XXX a paragraph followed by verbatim looks better if there is no blank
-- line between the paragraph and verbatim, otherwise there is extra blank
-- line in makeinfo output.
return $ text "@verbatim" $$
vcat (map text (lines str)) $$
text "@end verbatim\n"
@ -176,7 +164,7 @@ blockToTexinfo (OrderedList (start, numstyle, numdelim) lst) = do
items <- mapM listItemToTexinfo lst
return $ text "@enumerate " <> exemplar $$
vcat items $$
text "@end enumerate"
text "@end enumerate\n"
where
exemplar = case numstyle of
DefaultStyle -> decimal
@ -195,7 +183,7 @@ blockToTexinfo (DefinitionList lst) = do
items <- mapM defListItemToTexinfo lst
return $ text "@table @asis" $$
vcat items $$
text "@end table"
text "@end table\n"
blockToTexinfo HorizontalRule =
-- XXX can't get the equivalent from LaTeX.hs to work
@ -209,13 +197,13 @@ blockToTexinfo HorizontalRule =
blockToTexinfo (Header 0 lst) = do
txt <- if null lst
then return $ text "Top"
else inlineListToTexinfo (deVerb lst)
else inlineListToTexinfo lst
return $ text "@node Top" $$
text "@top " <> txt <> char '\n'
blockToTexinfo (Header level lst) = do
node <- inlineListForNode (deVerb lst)
txt <- inlineListToTexinfo (deVerb lst)
node <- inlineListForNode lst
txt <- inlineListToTexinfo lst
return $ if (level > 0) && (level <= 4)
then text "\n@node " <> node <> char '\n' <>
text (seccmd level) <> txt
@ -228,7 +216,7 @@ blockToTexinfo (Header level lst) = do
blockToTexinfo (Table caption aligns widths heads rows) = do
headers <- tableHeadToTexinfo aligns heads
captionText <- inlineListToTexinfo (deVerb caption)
captionText <- inlineListToTexinfo caption
rowsText <- mapM (tableRowToTexinfo aligns) rows
let colWidths = map (printf "%.2f ") widths
let colDescriptors = concat colWidths
@ -279,7 +267,7 @@ blockListToTexinfo [] = return $ empty
blockListToTexinfo (x:xs) = do
x' <- blockToTexinfo x
case x of
(Header level _) -> do
Header level _ -> do
-- We need need to insert a menu for this node.
let (before, after) = break isHeader xs
before' <- blockListToTexinfo before
@ -294,6 +282,11 @@ blockListToTexinfo (x:xs) = do
text "@end menu"
after' <- blockListToTexinfo after
return $ x' $$ before' $$ menu' $$ after'
Para x -> do
xs' <- blockListToTexinfo xs
case xs of
((CodeBlock _ _):_) -> return $ x' $$ xs'
_ -> return $ x' $$ text "" $$ xs'
_ -> do
xs' <- blockListToTexinfo xs
return $ x' $$ xs'
@ -316,7 +309,7 @@ collectNodes level (x:xs) =
makeMenuLine :: Block
-> State WriterState Doc
makeMenuLine (Header _ lst) = do
txt <- inlineListForNode (deVerb lst)
txt <- inlineListForNode lst
return $ text "* " <> txt <> text "::"
listItemToTexinfo :: [Block]
@ -327,7 +320,7 @@ listItemToTexinfo lst = blockListToTexinfo lst >>=
defListItemToTexinfo :: ([Inline], [Block])
-> State WriterState Doc
defListItemToTexinfo (term, def) = do
term' <- inlineListToTexinfo $ deVerb term
term' <- inlineListToTexinfo term
def' <- blockListToTexinfo def
return $ text "@item " <> term' <> text "\n" $$ def'
@ -342,12 +335,12 @@ inlineListForNode :: [Inline] -- ^ Inlines to convert
inlineListForNode lst = mapM inlineForNode lst >>= return . hcat
inlineForNode (Str str) = return $ text $ filter (not.disallowedInNode) str
inlineForNode (Emph lst) = inlineListForNode (deVerb lst)
inlineForNode (Strong lst) = inlineListForNode (deVerb lst)
inlineForNode (Strikeout lst) = inlineListForNode (deVerb lst)
inlineForNode (Superscript lst) = inlineListForNode (deVerb lst)
inlineForNode (Subscript lst) = inlineListForNode (deVerb lst)
inlineForNode (Quoted _ lst) = inlineListForNode (deVerb lst)
inlineForNode (Emph lst) = inlineListForNode lst
inlineForNode (Strong lst) = inlineListForNode lst
inlineForNode (Strikeout lst) = inlineListForNode lst
inlineForNode (Superscript lst) = inlineListForNode lst
inlineForNode (Subscript lst) = inlineListForNode lst
inlineForNode (Quoted _ lst) = inlineListForNode lst
inlineForNode (Code str) = inlineForNode (Str str)
inlineForNode Space = return $ char ' '
inlineForNode EmDash = return $ text "---"
@ -358,8 +351,8 @@ inlineForNode LineBreak = return empty
inlineForNode (Math _) = return empty
inlineForNode (TeX _) = return empty
inlineForNode (HtmlInline _) = return empty
inlineForNode (Link lst _) = inlineListForNode (deVerb lst)
inlineForNode (Image lst _) = inlineListForNode (deVerb lst)
inlineForNode (Link lst _) = inlineListForNode lst
inlineForNode (Image lst _) = inlineListForNode lst
inlineForNode (Note _) = return empty
-- XXX not sure what the complete set of illegal characters is.
@ -372,16 +365,16 @@ inlineToTexinfo :: Inline -- ^ Inline to convert
-> State WriterState Doc
inlineToTexinfo (Emph lst) =
inlineListToTexinfo (deVerb lst) >>= return . inCmd "emph"
inlineListToTexinfo lst >>= return . inCmd "emph"
inlineToTexinfo (Strong lst) =
inlineListToTexinfo (deVerb lst) >>= return . inCmd "strong"
inlineListToTexinfo lst >>= return . inCmd "strong"
inlineToTexinfo (Strikeout lst) = do
addToHeader $ "@macro textstrikeout{text}\n" ++
"~~\\text\\~~\n" ++
"@end macro\n"
contents <- inlineListToTexinfo $ deVerb lst
contents <- inlineListToTexinfo lst
return $ text "@textstrikeout{" <> contents <> text "}"
inlineToTexinfo (Superscript lst) = do
@ -393,7 +386,7 @@ inlineToTexinfo (Superscript lst) = do
"^@{\\text\\@}\n" ++
"@end ifnottex\n" ++
"@end macro\n"
contents <- inlineListToTexinfo $ deVerb lst
contents <- inlineListToTexinfo lst
return $ text "@textsuperscript{" <> contents <> char '}'
inlineToTexinfo (Subscript lst) = do
@ -405,12 +398,11 @@ inlineToTexinfo (Subscript lst) = do
"_@{\\text\\@}\n" ++
"@end ifnottex\n" ++
"@end macro\n"
contents <- inlineListToTexinfo $ deVerb lst
contents <- inlineListToTexinfo lst
return $ text "@textsubscript{" <> contents <> char '}'
inlineToTexinfo (Code str) = do
let chr = ((enumFromTo '!' '~') \\ str) !! 0
return $ text $ "@verb{" ++ [chr] ++ str ++ [chr] ++ "}"
return $ text $ "@code{" ++ stringToTexinfo str ++ "}"
inlineToTexinfo (Quoted SingleQuote lst) = do
contents <- inlineListToTexinfo lst
@ -435,13 +427,13 @@ inlineToTexinfo (Link txt (src, _)) = do
case txt of
[Code x] | x == src -> -- autolink
do return $ text $ "@url{" ++ x ++ "}"
_ -> do contents <- inlineListToTexinfo $ deVerb txt
_ -> do contents <- inlineListToTexinfo txt
let src1 = stringToTexinfo src
return $ text ("@uref{" ++ src1 ++ ",") <> contents <>
char '}'
inlineToTexinfo (Image alternate (source, tit)) = do
content <- inlineListToTexinfo $ deVerb alternate
content <- inlineListToTexinfo alternate
return $ text ("@image{" ++ base ++ ",,,") <> content <> text "," <>
text (ext ++ "}")
where

6
debian/control vendored
View file

@ -19,7 +19,7 @@ Description: general markup converter
another, and a command-line tool that uses this library. It can read
markdown and (subsets of) reStructuredText, HTML, and LaTeX, and it
can write markdown, reStructuredText, HTML, LaTeX, ConTeXt, DocBook,
RTF, groff man pages, and S5 HTML slide shows.
RTF, GNU Texinfo, groff man pages, and S5 HTML slide shows.
.
Pandoc extends standard markdown syntax with footnotes, embedded LaTeX,
tables, definition lists, and other features. A compatibility mode is
@ -44,7 +44,7 @@ Description: general markup converter
another, and a command-line tool that uses this library. It can read
markdown and (subsets of) reStructuredText, HTML, and LaTeX, and it
can write markdown, reStructuredText, HTML, LaTeX, ConTeXt, DocBook,
RTF, groff man pages, and S5 HTML slide shows.
RTF, GNU Texinfo, groff man pages, and S5 HTML slide shows.
.
Pandoc extends standard markdown syntax with footnotes, embedded LaTeX,
tables, definition lists, and other features. A compatibility mode is
@ -69,7 +69,7 @@ Description: general markup converter
another, and a command-line tool that uses this library. It can read
markdown and (subsets of) reStructuredText, HTML, and LaTeX, and it
can write markdown, reStructuredText, HTML, LaTeX, ConTeXt, DocBook,
RTF, groff man pages, and S5 HTML slide shows.
RTF, GNU Texinfo, groff man pages, and S5 HTML slide shows.
.
Pandoc extends standard markdown syntax with footnotes, embedded LaTeX,
tables, definition lists, and other features. A compatibility mode is

8
debian/copyright vendored
View file

@ -1,5 +1,5 @@
Pandoc
Copyright (C) 2006-7 John MacFarlane <jgm at berkeley dot edu>
Copyright (C) 2006-8 John MacFarlane <jgm at berkeley dot edu>
This code is released under the [GPL], version 2 or later:
@ -31,6 +31,12 @@ Pandoc includes some code from other authors. The copyright and license
statements for these sources are included below. All are GPL-compatible
licenses.
----------------------------------------------------------------------
Text/Pandoc/Writers/Texinfo.hs
Copyright (C) 2008 John MacFarlane and Peter Wang
Released under the GPL.
----------------------------------------------------------------------
UTF8.hs
Copyright (c) 2003, OGI School of Science & Engineering, Oregon Health &

View file

@ -1,7 +1,8 @@
Pandoc is a command-line tool for converting from one markup format
to another. It can read markdown and (subsets of) reStructuredText,
HTML, and LaTeX, and it can write markdown, reStructuredText, HTML,
LaTeX, ConTeXt, DocBook, RTF, groff man pages, and S5 HTML slide shows.
LaTeX, ConTeXt, DocBook, RTF, GNU Texinfo, groff man pages, and S5 HTML
slide shows.
Pandoc extends standard markdown syntax with footnotes, embedded LaTeX,
and other features. A compatibility mode is provided for those who

View file

@ -11,7 +11,7 @@ long_description \
Pandoc is a command-line tool for converting from one markup format \
to another. It can read markdown and (subsets of) reStructuredText, \
HTML, and LaTeX, and it can write markdown, reStructuredText, HTML, \
LaTeX, ConTeXt, DocBook, RTF, groff man pages, and S5 HTML slide shows.
LaTeX, ConTeXt, DocBook, RTF, Texinfo, groff man, and S5 HTML slide shows.
homepage http://johnmacfarlane.net/pandoc/
platforms darwin

View file

@ -14,8 +14,8 @@ pandoc [*options*] [*input-file*]...
Pandoc converts files from one markup format to another. It can
read markdown and (subsets of) reStructuredText, HTML, and LaTeX, and
it can write markdown, reStructuredText, HTML, LaTeX, ConTeXt, groff man,
RTF, DocBook XML, and S5 HTML slide shows.
it can write markdown, reStructuredText, HTML, LaTeX, ConTeXt, Texinfo,
groff man, RTF, DocBook XML, and S5 HTML slide shows.
If no *input-file* is specified, input is read from STDIN.
Otherwise, the *input-files* are concatenated (with a blank
@ -65,11 +65,10 @@ to Pandoc. Or use `html2markdown`(1), a wrapper around `pandoc`.
-t *FORMAT*, -w *FORMAT*, \--to=*FORMAT*, \--write=*FORMAT*
: Specify output format. *FORMAT* can be `native` (native Haskell),
`man` (groff man page),
`markdown` (markdown or plain text), `rst` (reStructuredText),
`html` (HTML), `latex` (LaTeX), `context` (ConTeXt), `man` (groff man),
`docbook` (DocBook XML), `s5` (S5 HTML and javascript slide show),
or `rtf` (rich text format).
`texinfo` (GNU Texinfo), `docbook` (DocBook XML),
`s5` (S5 HTML and javascript slide show), or `rtf` (rich text format).
-s, \--standalone
: Produce output with an appropriate header and footer (e.g. a

View file

@ -139,7 +139,6 @@ This is a block quote. It is pretty short.
@end quotation
@quotation
Code in a block quote:
@verbatim
sub status {
print "working";
@ -154,6 +153,7 @@ item one
@item
item two
@end enumerate
Nested block quotes:
@quotation
@ -179,7 +179,6 @@ And a following paragraph.
@node Code Blocks
@chapter Code Blocks
Code:
@verbatim
---- (should be four hyphens)
@ -191,7 +190,6 @@ this code block is indented by one tab
@end verbatim
And:
@verbatim
this code block is indented by two tabs
@ -305,6 +303,7 @@ Second
@item
Third
@end enumerate
and:
@enumerate
@ -315,6 +314,7 @@ Two
@item
Three
@end enumerate
Loose using tabs:
@enumerate
@ -328,6 +328,7 @@ Second
Third
@end enumerate
and using spaces:
@enumerate
@ -341,6 +342,7 @@ Two
Three
@end enumerate
Multiple paragraphs:
@enumerate
@ -357,6 +359,7 @@ Item 3.
@end enumerate
@node Nested
@section Nested
@itemize
@ -393,6 +396,7 @@ Foe
@item
Third
@end enumerate
Same thing but with paragraphs:
@enumerate
@ -416,6 +420,7 @@ Third
@end enumerate
@node Tabs and spaces
@section Tabs and spaces
@itemize
@ -458,8 +463,11 @@ a subsublist
@item
a subsublist
@end enumerate
@end enumerate
@end enumerate
Nesting:
@enumerate A
@ -475,9 +483,13 @@ Decimal start with 6
@item
Lower alpha with paren
@end enumerate
@end enumerate
@end enumerate
@end enumerate
Autonumbering:
@enumerate
@ -489,7 +501,9 @@ More.
@item
Nested.
@end enumerate
@end enumerate
Should not be a list item:
M.A. 2007
@ -518,6 +532,7 @@ orange fruit
yellow fruit
@end table
Tight using tabs:
@table @asis
@ -531,6 +546,7 @@ orange fruit
yellow fruit
@end table
Loose:
@table @asis
@ -547,6 +563,7 @@ orange fruit
yellow fruit
@end table
Multiple blocks with italics:
@table @asis
@ -559,7 +576,6 @@ contains seeds@comma{} crisp@comma{} pleasant to taste
@item @emph{orange}
orange fruit
@verbatim
{ orange code block }
@end verbatim
@ -570,6 +586,7 @@ orange block quote
@end quotation
@end table
@node HTML Blocks
@chapter HTML Blocks
Simple block on one line:
@ -587,7 +604,6 @@ Here's a simple block:
foo
This should be a code block@comma{} though:
@verbatim
<div>
foo
@ -595,7 +611,6 @@ This should be a code block@comma{} though:
@end verbatim
As should this:
@verbatim
<div>foo</div>
@end verbatim
@ -608,7 +623,6 @@ This should just be an HTML comment:
Multiline:
Code block:
@verbatim
<!-- Comment -->
@end verbatim
@ -616,7 +630,6 @@ Code block:
Just plain comment@comma{} with trailing spaces on the line:
Code:
@verbatim
<hr />
@end verbatim
@ -646,7 +659,7 @@ So is @strong{@emph{this}} word.
So is @strong{@emph{this}} word.
This is code: @verb{!>!}@comma{} @verb{!$!}@comma{} @verb{!\!}@comma{} @verb{!\$!}@comma{} @verb{!<html>!}.
This is code: @code{>}@comma{} @code{$}@comma{} @code{\}@comma{} @code{\$}@comma{} @code{<html>}.
@textstrikeout{This is @emph{strikeout}.}
@ -673,7 +686,7 @@ These should not be superscripts or subscripts@comma{} because of the unescaped
`He said@comma{} ``I want to go.''' Were you alive in the 70's?
Here is some quoted `@verb{!code!}' and a ``@uref{http://example.com/?foo=1&bar=2,quoted link}''.
Here is some quoted `@code{code}' and a ``@uref{http://example.com/?foo=1&bar=2,quoted link}''.
Some dashes: one---two---three---four---five.
@ -719,11 +732,11 @@ These shouldn't be math:
@itemize
@item
To get the famous equation@comma{} write @verb{!$e = mc^2$!}.
To get the famous equation@comma{} write @code{$e = mc^2$}.
@item
$22@comma{}000 is a @emph{lot} of money. So is $34@comma{}000. (It worked if ``lot'' is emphasized.)
@item
Escaped @verb{!$!}: $73 @emph{this should be emphasized} 23$.
Escaped @code{$}: $73 @emph{this should be emphasized} 23$.
@end itemize
Here's a LaTeX table:
@ -858,7 +871,6 @@ Indented @uref{/url,twice}.
Indented @uref{/url,thrice}.
This should [not][] be a link.
@verbatim
[not]: /url
@end verbatim
@ -892,14 +904,13 @@ In a list?
It should.
@end itemize
An e-mail address: @uref{mailto:nobody@@nowhere.net,@verb{!nobody@@nowhere.net!}}
An e-mail address: @uref{mailto:nobody@@nowhere.net,@code{nobody@@nowhere.net}}
@quotation
Blockquoted: @url{http://example.com/}
@end quotation
Auto-links should not occur here: @verb{!<http://example.com/>!}
Auto-links should not occur here: @code{<http://example.com/>}
@verbatim
or here: <http://example.com/>
@end verbatim
@ -931,12 +942,11 @@ Here is a movie @image{movie,,,movie,jpg} icon.
Here is a footnote reference@comma{}@footnote{Here is the footnote. It can go anywhere after the footnote reference. It need not be placed at the end of the document.} and another.@footnote{Here's the long note. This one contains multiple blocks.
Subsequent blocks are indented to show that they belong to the footnote (as with list items).
@verbatim
{ <code> }
@end verbatim
If you want@comma{} you can indent every line@comma{} but you can also be lazy and just indent the first line of each block.} This should @emph{not} be a footnote reference@comma{} because it contains a space.[^my note] Here is an inline note.@footnote{This is @emph{easier} to type. Inline notes may contain @uref{http://google.com,links} and @verb{!]!} verbatim characters@comma{} as well as [bracketed text].}
If you want@comma{} you can indent every line@comma{} but you can also be lazy and just indent the first line of each block.} This should @emph{not} be a footnote reference@comma{} because it contains a space.[^my note] Here is an inline note.@footnote{This is @emph{easier} to type. Inline notes may contain @uref{http://google.com,links} and @code{]} verbatim characters@comma{} as well as [bracketed text].}
@quotation
Notes can go in quotes.@footnote{In quote.}
@ -946,6 +956,7 @@ Notes can go in quotes.@footnote{In quote.}
@item
And in list items.@footnote{In list.}
@end enumerate
This paragraph should not be part of the note@comma{} as it is not indented.
@bye

View file

@ -87,3 +87,10 @@ click on the name of the output file:
@ pandoc @@code.text@@ -s -o @@example18.html@@
19. GNU Texinfo, converted to info, HTML, and PDF formats:
@ pandoc @@README@@ -s -o @@example19.texi@@
@ makeinfo @@example19.texi@@ -o @@example19.info@@
@ makeinfo @@example19.texi@@ --html -o @@example19@@
@ texi2pdf @@example19.texi@@ # produces @@example19.pdf@@

View file

@ -6,7 +6,7 @@ Pandoc is a [Haskell] library for converting from one markup format
to another, and a command-line tool that uses this library. It can read
[markdown] and (subsets of) [reStructuredText], [HTML], and [LaTeX],
and it can write [markdown], [reStructuredText], [HTML], [LaTeX], [ConTeXt],
[RTF], [DocBook XML], [groff man], and [S5] HTML slide shows.
[RTF], [DocBook XML], [GNU Texinfo], [groff man], and [S5] HTML slide shows.
Pandoc features
@ -168,6 +168,7 @@ kind.
[RTF]: http://en.wikipedia.org/wiki/Rich_Text_Format
[DocBook XML]: http://www.docbook.org/
[groff man]: http://developer.apple.com/DOCUMENTATION/Darwin/Reference/ManPages/man7/groff_man.7.html
[GNU Texinfo]: http://www.gnu.org/software/texinfo/
[Haskell]: http://www.haskell.org/
[GHC]: http://www.haskell.org/ghc/
[GPL]: http://www.gnu.org/copyleft/gpl.html