Committed novalazy's initial patch for texinfo output,

including tests for texinfo writer.


git-svn-id: https://pandoc.googlecode.com/svn/trunk@1243 788f1e2b-df1e-0410-8736-df70ead52e1b
This commit is contained in:
fiddlosopher 2008-02-24 05:48:41 +00:00
parent 270eb7bed4
commit 49e0e507b7
7 changed files with 1541 additions and 1 deletions

View file

@ -83,6 +83,7 @@ writers = [("native" , (writeDoc, ""))
,("docbook" , (writeDocbook, defaultDocbookHeader))
,("latex" , (writeLaTeX, defaultLaTeXHeader))
,("context" , (writeConTeXt, defaultConTeXtHeader))
,("texinfo" , (writeTexinfo, ""))
,("man" , (writeMan, ""))
,("markdown" , (writeMarkdown, ""))
,("rst" , (writeRST, ""))

View file

@ -68,6 +68,7 @@ module Text.Pandoc
, writeRST
, writeLaTeX
, writeConTeXt
, writeTexinfo
, writeHtml
, writeHtmlString
, writeS5
@ -96,6 +97,7 @@ import Text.Pandoc.Writers.Markdown
import Text.Pandoc.Writers.RST
import Text.Pandoc.Writers.LaTeX
import Text.Pandoc.Writers.ConTeXt
import Text.Pandoc.Writers.Texinfo
import Text.Pandoc.Writers.HTML
import Text.Pandoc.Writers.S5
import Text.Pandoc.Writers.Docbook

View file

@ -0,0 +1,461 @@
{-
Copyright (C) 2008 John MacFarlane and Peter Wang
This program is free software; you can redistribute it and/or modify
it under the terms of the GNU General Public License as published by
the Free Software Foundation; either version 2 of the License, or
(at your option) any later version.
This program is distributed in the hope that it will be useful,
but WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
GNU General Public License for more details.
You should have received a copy of the GNU General Public License
along with this program; if not, write to the Free Software
Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
-}
{- |
Module : Text.Pandoc.Writers.Texinfo
Copyright : Copyright (C) 2008 John MacFarlane and Peter Wang
License : GNU GPL, version 2 or above
Maintainer : John MacFarlane <jgm@berkeley.edu>
Stability : alpha
Portability : portable
Conversion of 'Pandoc' format into Texinfo.
-}
module Text.Pandoc.Writers.Texinfo ( writeTexinfo ) where
import Text.Pandoc.Definition
import Text.Pandoc.Shared
import Text.Printf ( printf )
import Data.List ( (\\), isSuffixOf )
import Data.Char ( toLower, chr, ord )
import qualified Data.Set as S
import Control.Monad.State
import Text.PrettyPrint.HughesPJ hiding ( Str )
data WriterState =
WriterState { stIncludes :: S.Set String -- strings to include in header
}
{- TODO:
- internal cross references a la HTML
- generated .texi files don't work when run through texi2dvi
-}
-- | Add line to header.
addToHeader :: String -> State WriterState ()
addToHeader str = do
st <- get
let includes = stIncludes st
put st {stIncludes = S.insert str includes}
-- | Convert Pandoc to Texinfo.
writeTexinfo :: WriterOptions -> Pandoc -> String
writeTexinfo options document =
render $ evalState (pandocToTexinfo options $ wrapTop document) $
WriterState { stIncludes = S.empty }
-- | Add a "Top" node around the document, needed by Texinfo.
wrapTop (Pandoc (Meta title authors date) blocks) =
Pandoc (Meta title authors date) (Header 0 title : blocks)
pandocToTexinfo :: WriterOptions -> Pandoc -> State WriterState Doc
pandocToTexinfo options (Pandoc meta blocks) = do
main <- blockListToTexinfo blocks
head <- if writerStandalone options
then texinfoHeader options meta
else return empty
let before = if null (writerIncludeBefore options)
then empty
else text (writerIncludeBefore options)
let after = if null (writerIncludeAfter options)
then empty
else text (writerIncludeAfter options)
let body = before $$ main $$ after
-- XXX toc untested
let toc = if writerTableOfContents options
then text "@contents"
else empty
let foot = if writerStandalone options
then text "@bye"
else empty
return $ head $$ toc $$ body $$ foot
-- | Insert bibliographic information into Texinfo header.
texinfoHeader :: WriterOptions -- ^ Options, including Texinfo header
-> Meta -- ^ Meta with bibliographic information
-> State WriterState Doc
texinfoHeader options (Meta title authors date) = do
titletext <- if null title
then return empty
else do
t <- inlineListToTexinfo title
return $ text "@title " <> t
headerIncludes <- get >>= return . S.toList . stIncludes
let extras = text $ unlines headerIncludes
let authorstext = map makeAuthor authors
let datetext = if date == ""
then empty
else text $ stringToTexinfo date
let baseHeader = text $ writerHeader options
let header = baseHeader $$ extras
return $ text "\\input texinfo" $$
header $$
text "@ifnottex" $$
text "@paragraphindent 0" $$
text "@end ifnottex" $$
text "@titlepage" $$
titletext $$ vcat authorstext $$
datetext $$
text "@end titlepage"
makeAuthor author = text $ "@author " ++ (stringToTexinfo author)
-- | Escape things as needed for Texinfo.
stringToTexinfo :: String -> String
stringToTexinfo = escapeStringUsing texinfoEscapes
where texinfoEscapes = [ ('{', "@{")
, ('}', "@}")
, ('@', "@@")
, (',', "@comma{}") -- only needed in argument lists
]
-- | Puts contents into Texinfo command.
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
blockToTexinfo Null = return empty
blockToTexinfo (Plain lst) =
inlineListToTexinfo lst
blockToTexinfo (Para lst) = do
result <- inlineListToTexinfo lst
return $ result <> char '\n'
blockToTexinfo (BlockQuote lst) = do
contents <- blockListToTexinfo lst
return $ text "@quotation" $$
contents $$
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"
blockToTexinfo (RawHtml str) = return empty
blockToTexinfo (BulletList lst) = do
items <- mapM listItemToTexinfo lst
return $ text "@itemize" $$
vcat items $$
text "@end itemize\n"
blockToTexinfo (OrderedList (start, numstyle, numdelim) lst) = do
items <- mapM listItemToTexinfo lst
return $ text "@enumerate " <> exemplar $$
vcat items $$
text "@end enumerate"
where
exemplar = case numstyle of
DefaultStyle -> decimal
Decimal -> decimal
UpperRoman -> decimal -- Roman numerals not supported
LowerRoman -> decimal
UpperAlpha -> upperAlpha
LowerAlpha -> lowerAlpha
decimal = if start == 1
then empty
else text (show start)
upperAlpha = text [chr $ ord 'A' + start - 1]
lowerAlpha = text [chr $ ord 'a' + start - 1]
blockToTexinfo (DefinitionList lst) = do
items <- mapM defListItemToTexinfo lst
return $ text "@table @asis" $$
vcat items $$
text "@end table"
blockToTexinfo HorizontalRule =
-- XXX can't get the equivalent from LaTeX.hs to work
return $ text "@iftex" $$
text "@bigskip@hrule@bigskip" $$
text "@end iftex" $$
text "@ifnottex" $$
text (take 72 $ repeat '-') $$
text "@end ifnottex"
blockToTexinfo (Header 0 lst) = do
txt <- if null lst
then return $ text "Top"
else inlineListToTexinfo (deVerb lst)
return $ text "@node Top" $$
text "@top " <> txt <> char '\n'
blockToTexinfo (Header level lst) = do
node <- inlineListForNode (deVerb lst)
txt <- inlineListToTexinfo (deVerb lst)
return $ if (level > 0) && (level <= 4)
then text "\n@node " <> node <> char '\n' <>
text (seccmd level) <> txt
else txt
where
seccmd 1 = "@chapter "
seccmd 2 = "@section "
seccmd 3 = "@subsection "
seccmd 4 = "@subsubsection "
blockToTexinfo (Table caption aligns widths heads rows) = do
headers <- tableHeadToTexinfo aligns heads
captionText <- inlineListToTexinfo (deVerb caption)
rowsText <- mapM (tableRowToTexinfo aligns) rows
let colWidths = map (printf "%.2f ") widths
let colDescriptors = concat colWidths
let tableBody = text ("@multitable @columnfractions " ++ colDescriptors) $$
headers $$
vcat rowsText $$
text "@end multitable"
return $ if isEmpty captionText
then tableBody <> char '\n'
else text "@float" $$
tableBody $$
inCmd "caption" captionText $$
text "@end float"
tableHeadToTexinfo = tableAnyRowToTexinfo "@headitem "
tableRowToTexinfo = tableAnyRowToTexinfo "@item "
tableAnyRowToTexinfo :: String
-> [Alignment]
-> [[Block]]
-> State WriterState Doc
tableAnyRowToTexinfo itemtype aligns cols =
zipWithM alignedBlock aligns cols >>=
return . (text itemtype $$) . foldl (\row item -> row $$
(if isEmpty row then empty else text " @tab ") <> item) empty
alignedBlock :: Alignment
-> [Block]
-> State WriterState Doc
-- XXX @flushleft and @flushright text won't get word wrapped. Since word
-- wrapping is more important than alignment, we ignore the alignment.
alignedBlock _ = blockListToTexinfo
{-
alignedBlock AlignLeft col = do
b <- blockListToTexinfo col
return $ text "@flushleft" $$ b $$ text "@end flushleft"
alignedBlock AlignRight col = do
b <- blockListToTexinfo col
return $ text "@flushright" $$ b $$ text "@end flushright"
alignedBlock _ col = blockListToTexinfo col
-}
-- | Convert Pandoc block elements to Texinfo.
blockListToTexinfo :: [Block]
-> State WriterState Doc
blockListToTexinfo [] = return $ empty
blockListToTexinfo (x:xs) = do
x' <- blockToTexinfo x
case x of
(Header level _) -> do
-- We need need to insert a menu for this node.
let (before, after) = break isHeader xs
before' <- blockListToTexinfo before
let menu = if level < 4
then collectNodes (level + 1) after
else []
lines <- mapM makeMenuLine menu
let menu' = if null lines
then empty
else text "@menu" $$
vcat lines $$
text "@end menu"
after' <- blockListToTexinfo after
return $ x' $$ before' $$ menu' $$ after'
_ -> do
xs' <- blockListToTexinfo xs
return $ x' $$ xs'
isHeader (Header _ _) = True
isHeader _ = False
collectNodes level [] = []
collectNodes level (x:xs) =
case x of
(Header hl _) ->
if hl < level
then []
else if hl == level
then x : collectNodes level xs
else collectNodes level xs
_ ->
collectNodes level xs
makeMenuLine :: Block
-> State WriterState Doc
makeMenuLine (Header _ lst) = do
txt <- inlineListForNode (deVerb lst)
return $ text "* " <> txt <> text "::"
listItemToTexinfo :: [Block]
-> State WriterState Doc
listItemToTexinfo lst = blockListToTexinfo lst >>=
return . (text "@item" $$)
defListItemToTexinfo :: ([Inline], [Block])
-> State WriterState Doc
defListItemToTexinfo (term, def) = do
term' <- inlineListToTexinfo $ deVerb term
def' <- blockListToTexinfo def
return $ text "@item " <> term' <> text "\n" $$ def'
-- | Convert list of inline elements to Texinfo.
inlineListToTexinfo :: [Inline] -- ^ Inlines to convert
-> State WriterState Doc
inlineListToTexinfo lst = mapM inlineToTexinfo lst >>= return . hcat
-- | Convert list of inline elements to Texinfo acceptable for a node name.
inlineListForNode :: [Inline] -- ^ Inlines to convert
-> State WriterState Doc
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 (Code str) = inlineForNode (Str str)
inlineForNode Space = return $ char ' '
inlineForNode EmDash = return $ text "---"
inlineForNode EnDash = return $ text "--"
inlineForNode Apostrophe = return $ char '\''
inlineForNode Ellipses = return $ text "..."
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 (Note _) = return empty
-- XXX not sure what the complete set of illegal characters is.
disallowedInNode '.' = True
disallowedInNode ',' = True
disallowedInNode _ = False
-- | Convert inline element to Texinfo
inlineToTexinfo :: Inline -- ^ Inline to convert
-> State WriterState Doc
inlineToTexinfo (Emph lst) =
inlineListToTexinfo (deVerb lst) >>= return . inCmd "emph"
inlineToTexinfo (Strong lst) =
inlineListToTexinfo (deVerb lst) >>= return . inCmd "strong"
inlineToTexinfo (Strikeout lst) = do
addToHeader $ "@macro textstrikeout{text}\n" ++
"~~\\text\\~~\n" ++
"@end macro\n"
contents <- inlineListToTexinfo $ deVerb lst
return $ text "@textstrikeout{" <> contents <> text "}"
inlineToTexinfo (Superscript lst) = do
addToHeader $ "@macro textsuperscript{text}\n" ++
"@iftex\n" ++
"@textsuperscript{\\text\\}\n" ++
"@end iftex\n" ++
"@ifnottex\n" ++
"^@{\\text\\@}\n" ++
"@end ifnottex\n" ++
"@end macro\n"
contents <- inlineListToTexinfo $ deVerb lst
return $ text "@textsuperscript{" <> contents <> char '}'
inlineToTexinfo (Subscript lst) = do
addToHeader $ "@macro textsubscript{text}\n" ++
"@iftex\n" ++
"@textsubscript{\\text\\}\n" ++
"@end iftex\n" ++
"@ifnottex\n" ++
"_@{\\text\\@}\n" ++
"@end ifnottex\n" ++
"@end macro\n"
contents <- inlineListToTexinfo $ deVerb lst
return $ text "@textsubscript{" <> contents <> char '}'
inlineToTexinfo (Code str) = do
let chr = ((enumFromTo '!' '~') \\ str) !! 0
return $ text $ "@verb{" ++ [chr] ++ str ++ [chr] ++ "}"
inlineToTexinfo (Quoted SingleQuote lst) = do
contents <- inlineListToTexinfo lst
return $ char '`' <> contents <> char '\''
inlineToTexinfo (Quoted DoubleQuote lst) = do
contents <- inlineListToTexinfo lst
return $ text "``" <> contents <> text "''"
inlineToTexinfo Apostrophe = return $ char '\''
inlineToTexinfo EmDash = return $ text "---"
inlineToTexinfo EnDash = return $ text "--"
inlineToTexinfo Ellipses = return $ text "@dots{}"
inlineToTexinfo (Str str) = return $ text (stringToTexinfo str)
inlineToTexinfo (Math str) = return $ inCmd "math" $ text str
inlineToTexinfo (TeX str) = return $ text "@tex" $$ text str $$ text "@end tex"
inlineToTexinfo (HtmlInline str) = return empty
inlineToTexinfo (LineBreak) = return $ text "@*"
inlineToTexinfo Space = return $ char ' '
inlineToTexinfo (Link txt (src, _)) = do
case txt of
[Code x] | x == src -> -- autolink
do return $ text $ "@url{" ++ x ++ "}"
_ -> do contents <- inlineListToTexinfo $ deVerb txt
let src1 = stringToTexinfo src
return $ text ("@uref{" ++ src1 ++ ",") <> contents <>
char '}'
inlineToTexinfo (Image alternate (source, tit)) = do
content <- inlineListToTexinfo $ deVerb alternate
return $ text ("@image{" ++ base ++ ",,,") <> content <> text "," <>
text (ext ++ "}")
where
(revext, revbase) = break (=='.') (reverse source)
ext = reverse revext
base = case revbase of
('.' : rest) -> reverse rest
_ -> reverse revbase
inlineToTexinfo (Note contents) = do
contents' <- blockListToTexinfo contents
let rawnote = stripTrailingNewlines $ render contents'
let optNewline = "@end verbatim" `isSuffixOf` rawnote
return $ text "@footnote{" <>
text rawnote <>
(if optNewline then char '\n' else empty) <>
char '}'

View file

@ -5,6 +5,7 @@
../pandoc -r native -s -w rst testsuite.native > writer.rst
../pandoc -r native -s -w html testsuite.native > writer.html
../pandoc -r native -s -w latex testsuite.native > writer.latex
../pandoc -r native -s -w texinfo testsuite.native > writer.texinfo
../pandoc -r native -s -w rtf testsuite.native > writer.rtf
../pandoc -r native -s -w man testsuite.native > writer.man
sed -e '/^, Header 1 \[Str "HTML",Space,Str "Blocks"\]/,/^, HorizontalRule/d' testsuite.native | ../pandoc -r native -w docbook -s > writer.docbook

View file

@ -14,7 +14,7 @@ unless (-x $script) { die "$script is not executable.\n"; }
print "Writer tests:\n";
my @writeformats = ("html", "latex", "rst", "rtf", "markdown", "man", "native"); # docbook, context, and s5 handled separately
my @writeformats = ("html", "latex", "texinfo", "rst", "rtf", "markdown", "man", "native"); # docbook, context, and s5 handled separately
my $source = "testsuite.native";
sub test_results

124
tests/tables.texinfo Normal file
View file

@ -0,0 +1,124 @@
@node Top
@top Top
Simple table with caption:
@float
@multitable @columnfractions 0.15 0.09 0.16 0.13
@headitem
Right
@tab Left
@tab Center
@tab Default
@item
12
@tab 12
@tab 12
@tab 12
@item
123
@tab 123
@tab 123
@tab 123
@item
1
@tab 1
@tab 1
@tab 1
@end multitable
@caption{Demonstration of simple table syntax.}
@end float
Simple table without caption:
@multitable @columnfractions 0.15 0.09 0.16 0.13
@headitem
Right
@tab Left
@tab Center
@tab Default
@item
12
@tab 12
@tab 12
@tab 12
@item
123
@tab 123
@tab 123
@tab 123
@item
1
@tab 1
@tab 1
@tab 1
@end multitable
Simple table indented two spaces:
@float
@multitable @columnfractions 0.15 0.09 0.16 0.13
@headitem
Right
@tab Left
@tab Center
@tab Default
@item
12
@tab 12
@tab 12
@tab 12
@item
123
@tab 123
@tab 123
@tab 123
@item
1
@tab 1
@tab 1
@tab 1
@end multitable
@caption{Demonstration of simple table syntax.}
@end float
Multiline table with caption:
@float
@multitable @columnfractions 0.15 0.14 0.16 0.34
@headitem
Centered Header
@tab Left Aligned
@tab Right Aligned
@tab Default aligned
@item
First
@tab row
@tab 12.0
@tab Example of a row that spans multiple lines.
@item
Second
@tab row
@tab 5.0
@tab Here's another one. Note the blank line between rows.
@end multitable
@caption{Here's the caption. It may span multiple lines.}
@end float
Multiline table without caption:
@multitable @columnfractions 0.15 0.14 0.16 0.34
@headitem
Centered Header
@tab Left Aligned
@tab Right Aligned
@tab Default aligned
@item
First
@tab row
@tab 12.0
@tab Example of a row that spans multiple lines.
@item
Second
@tab row
@tab 5.0
@tab Here's another one. Note the blank line between rows.
@end multitable

951
tests/writer.texinfo Normal file
View file

@ -0,0 +1,951 @@
\input texinfo
@macro textstrikeout{text}
~~\text\~~
@end macro
@macro textsubscript{text}
@iftex
@textsubscript{\text\}
@end iftex
@ifnottex
_@{\text\@}
@end ifnottex
@end macro
@macro textsuperscript{text}
@iftex
@textsuperscript{\text\}
@end iftex
@ifnottex
^@{\text\@}
@end ifnottex
@end macro
@ifnottex
@paragraphindent 0
@end ifnottex
@titlepage
@title Pandoc Test Suite
@author John MacFarlane
@author Anonymous
July 17@comma{} 2006
@end titlepage
@node Top
@top Pandoc Test Suite
This is a set of tests for pandoc. Most of them are adapted from John Gruber's markdown test suite.
@iftex
@bigskip@hrule@bigskip
@end iftex
@ifnottex
------------------------------------------------------------------------
@end ifnottex
@menu
* Headers::
* Level 1::
* Paragraphs::
* Block Quotes::
* Code Blocks::
* Lists::
* Definition Lists::
* HTML Blocks::
* Inline Markup::
* Smart quotes ellipses dashes::
* LaTeX::
* Special Characters::
* Links::
* Images::
* Footnotes::
@end menu
@node Headers
@chapter Headers
@menu
* Level 2 with an embedded link::
@end menu
@node Level 2 with an embedded link
@section Level 2 with an @uref{/url,embedded link}
@menu
* Level 3 with emphasis::
@end menu
@node Level 3 with emphasis
@subsection Level 3 with @emph{emphasis}
@menu
* Level 4::
@end menu
@node Level 4
@subsubsection Level 4
Level 5
@node Level 1
@chapter Level 1
@menu
* Level 2 with emphasis::
* Level 2::
@end menu
@node Level 2 with emphasis
@section Level 2 with @emph{emphasis}
@menu
* Level 3::
@end menu
@node Level 3
@subsection Level 3
with no blank line
@node Level 2
@section Level 2
with no blank line
@iftex
@bigskip@hrule@bigskip
@end iftex
@ifnottex
------------------------------------------------------------------------
@end ifnottex
@node Paragraphs
@chapter Paragraphs
Here's a regular paragraph.
In Markdown 1.0.0 and earlier. Version 8. This line turns into a list item. Because a hard-wrapped line in the middle of a paragraph looked like a list item.
Here's one with a bullet. * criminey.
There should be a hard line break@*here.
@iftex
@bigskip@hrule@bigskip
@end iftex
@ifnottex
------------------------------------------------------------------------
@end ifnottex
@node Block Quotes
@chapter Block Quotes
E-mail style:
@quotation
This is a block quote. It is pretty short.
@end quotation
@quotation
Code in a block quote:
@verbatim
sub status {
print "working";
}
@end verbatim
A list:
@enumerate
@item
item one
@item
item two
@end enumerate
Nested block quotes:
@quotation
nested
@end quotation
@quotation
nested
@end quotation
@end quotation
This should not be a block quote: 2 > 1.
And a following paragraph.
@iftex
@bigskip@hrule@bigskip
@end iftex
@ifnottex
------------------------------------------------------------------------
@end ifnottex
@node Code Blocks
@chapter Code Blocks
Code:
@verbatim
---- (should be four hyphens)
sub status {
print "working";
}
this code block is indented by one tab
@end verbatim
And:
@verbatim
this code block is indented by two tabs
These should not be escaped: \$ \\ \> \[ \{
@end verbatim
@iftex
@bigskip@hrule@bigskip
@end iftex
@ifnottex
------------------------------------------------------------------------
@end ifnottex
@node Lists
@chapter Lists
@menu
* Unordered::
* Ordered::
* Nested::
* Tabs and spaces::
* Fancy list markers::
@end menu
@node Unordered
@section Unordered
Asterisks tight:
@itemize
@item
asterisk 1
@item
asterisk 2
@item
asterisk 3
@end itemize
Asterisks loose:
@itemize
@item
asterisk 1
@item
asterisk 2
@item
asterisk 3
@end itemize
Pluses tight:
@itemize
@item
Plus 1
@item
Plus 2
@item
Plus 3
@end itemize
Pluses loose:
@itemize
@item
Plus 1
@item
Plus 2
@item
Plus 3
@end itemize
Minuses tight:
@itemize
@item
Minus 1
@item
Minus 2
@item
Minus 3
@end itemize
Minuses loose:
@itemize
@item
Minus 1
@item
Minus 2
@item
Minus 3
@end itemize
@node Ordered
@section Ordered
Tight:
@enumerate
@item
First
@item
Second
@item
Third
@end enumerate
and:
@enumerate
@item
One
@item
Two
@item
Three
@end enumerate
Loose using tabs:
@enumerate
@item
First
@item
Second
@item
Third
@end enumerate
and using spaces:
@enumerate
@item
One
@item
Two
@item
Three
@end enumerate
Multiple paragraphs:
@enumerate
@item
Item 1@comma{} graf one.
Item 1. graf two. The quick brown fox jumped over the lazy dog's back.
@item
Item 2.
@item
Item 3.
@end enumerate
@node Nested
@section Nested
@itemize
@item
Tab
@itemize
@item
Tab
@itemize
@item
Tab
@end itemize
@end itemize
@end itemize
Here's another:
@enumerate
@item
First
@item
Second:
@itemize
@item
Fee
@item
Fie
@item
Foe
@end itemize
@item
Third
@end enumerate
Same thing but with paragraphs:
@enumerate
@item
First
@item
Second:
@itemize
@item
Fee
@item
Fie
@item
Foe
@end itemize
@item
Third
@end enumerate
@node Tabs and spaces
@section Tabs and spaces
@itemize
@item
this is a list item indented with tabs
@item
this is a list item indented with spaces
@itemize
@item
this is an example list item indented with tabs
@item
this is an example list item indented with spaces
@end itemize
@end itemize
@node Fancy list markers
@section Fancy list markers
@enumerate 2
@item
begins with 2
@item
and now 3
with a continuation
@enumerate 4
@item
sublist with roman numerals@comma{} starting with 4
@item
more items
@enumerate A
@item
a subsublist
@item
a subsublist
@end enumerate
@end enumerate
@end enumerate
Nesting:
@enumerate A
@item
Upper Alpha
@enumerate
@item
Upper Roman.
@enumerate 6
@item
Decimal start with 6
@enumerate c
@item
Lower alpha with paren
@end enumerate
@end enumerate
@end enumerate
@end enumerate
Autonumbering:
@enumerate
@item
Autonumber.
@item
More.
@enumerate
@item
Nested.
@end enumerate
@end enumerate
Should not be a list item:
M.A. 2007
B. Williams
@iftex
@bigskip@hrule@bigskip
@end iftex
@ifnottex
------------------------------------------------------------------------
@end ifnottex
@node Definition Lists
@chapter Definition Lists
Tight using spaces:
@table @asis
@item apple
red fruit
@item orange
orange fruit
@item banana
yellow fruit
@end table
Tight using tabs:
@table @asis
@item apple
red fruit
@item orange
orange fruit
@item banana
yellow fruit
@end table
Loose:
@table @asis
@item apple
red fruit
@item orange
orange fruit
@item banana
yellow fruit
@end table
Multiple blocks with italics:
@table @asis
@item @emph{apple}
red fruit
contains seeds@comma{} crisp@comma{} pleasant to taste
@item @emph{orange}
orange fruit
@verbatim
{ orange code block }
@end verbatim
@quotation
orange block quote
@end quotation
@end table
@node HTML Blocks
@chapter HTML Blocks
Simple block on one line:
foo
And nested without indentation:
foo
bar
Interpreted markdown in a table:
This is @emph{emphasized}
And this is @strong{strong}
Here's a simple block:
foo
This should be a code block@comma{} though:
@verbatim
<div>
foo
</div>
@end verbatim
As should this:
@verbatim
<div>foo</div>
@end verbatim
Now@comma{} nested:
foo
This should just be an HTML comment:
Multiline:
Code block:
@verbatim
<!-- Comment -->
@end verbatim
Just plain comment@comma{} with trailing spaces on the line:
Code:
@verbatim
<hr />
@end verbatim
Hr's:
@iftex
@bigskip@hrule@bigskip
@end iftex
@ifnottex
------------------------------------------------------------------------
@end ifnottex
@node Inline Markup
@chapter Inline Markup
This is @emph{emphasized}@comma{} and so @emph{is this}.
This is @strong{strong}@comma{} and so @strong{is this}.
An @emph{@uref{/url,emphasized link}}.
@strong{@emph{This is strong and em.}}
So is @strong{@emph{this}} word.
@strong{@emph{This is strong and em.}}
So is @strong{@emph{this}} word.
This is code: @verb{!>!}@comma{} @verb{!$!}@comma{} @verb{!\!}@comma{} @verb{!\$!}@comma{} @verb{!<html>!}.
@textstrikeout{This is @emph{strikeout}.}
Superscripts: a@textsuperscript{bc}d a@textsuperscript{@emph{hello}} a@textsuperscript{hello there}.
Subscripts: H@textsubscript{2}O@comma{} H@textsubscript{23}O@comma{} H@textsubscript{many of them}O.
These should not be superscripts or subscripts@comma{} because of the unescaped spaces: a^b c^d@comma{} a~b c~d.
@iftex
@bigskip@hrule@bigskip
@end iftex
@ifnottex
------------------------------------------------------------------------
@end ifnottex
@node Smart quotes ellipses dashes
@chapter Smart quotes@comma{} ellipses@comma{} dashes
``Hello@comma{}'' said the spider. ```Shelob' is my name.''
`A'@comma{} `B'@comma{} and `C' are letters.
`Oak@comma{}' `elm@comma{}' and `beech' are names of trees. So is `pine.'
`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}''.
Some dashes: one---two---three---four---five.
Dashes between numbers: 5--7@comma{} 255--66@comma{} 1987--1999.
Ellipses@dots{}and@dots{}and@dots{}.
@iftex
@bigskip@hrule@bigskip
@end iftex
@ifnottex
------------------------------------------------------------------------
@end ifnottex
@node LaTeX
@chapter LaTeX
@itemize
@item
@tex
\cite[22-23]{smith.1899}
@end tex
@item
@tex
\doublespacing
@end tex
@item
@math{2+2=4}
@item
@math{x \in y}
@item
@math{\alpha \wedge \omega}
@item
@math{223}
@item
@math{p}-Tree
@item
@math{\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}}
@item
Here's one that has a line break in it: @math{\alpha + \omega \times x^2}.
@end itemize
These shouldn't be math:
@itemize
@item
To get the famous equation@comma{} write @verb{!$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$.
@end itemize
Here's a LaTeX table:
@tex
\begin{tabular}{|l|l|}\hline
Animal & Number \\ \hline
Dog & 2 \\
Cat & 1 \\ \hline
\end{tabular}
@end tex
@iftex
@bigskip@hrule@bigskip
@end iftex
@ifnottex
------------------------------------------------------------------------
@end ifnottex
@node Special Characters
@chapter Special Characters
Here is some unicode:
@itemize
@item
I hat: Î
@item
o umlaut: ö
@item
section: §
@item
set membership: ∈
@item
copyright: ©
@end itemize
AT&T has an ampersand in their name.
AT&T is another way to write it.
This & that.
4 < 5.
6 > 5.
Backslash: \
Backtick: `
Asterisk: *
Underscore: _
Left brace: @{
Right brace: @}
Left bracket: [
Right bracket: ]
Left paren: (
Right paren: )
Greater-than: >
Hash: #
Period: .
Bang: !
Plus: +
Minus: -
@iftex
@bigskip@hrule@bigskip
@end iftex
@ifnottex
------------------------------------------------------------------------
@end ifnottex
@node Links
@chapter Links
@menu
* Explicit::
* Reference::
* With ampersands::
* Autolinks::
@end menu
@node Explicit
@section Explicit
Just a @uref{/url/,URL}.
@uref{/url/,URL and title}.
@uref{/url/,URL and title}.
@uref{/url/,URL and title}.
@uref{/url/,URL and title}
@uref{/url/,URL and title}
@uref{/url/with_underscore,with_underscore}
@uref{mailto:nobody@@nowhere.net,Email link}
@uref{,Empty}.
@node Reference
@section Reference
Foo @uref{/url/,bar}.
Foo @uref{/url/,bar}.
Foo @uref{/url/,bar}.
With @uref{/url/,embedded [brackets]}.
@uref{/url/,b} by itself should be a link.
Indented @uref{/url,once}.
Indented @uref{/url,twice}.
Indented @uref{/url,thrice}.
This should [not][] be a link.
@verbatim
[not]: /url
@end verbatim
Foo @uref{/url/,bar}.
Foo @uref{/url/,biz}.
@node With ampersands
@section With ampersands
Here's a @uref{http://example.com/?foo=1&bar=2,link with an ampersand in the URL}.
Here's a link with an amersand in the link text: @uref{http://att.com/,AT&T}.
Here's an @uref{/script?foo=1&bar=2,inline link}.
Here's an @uref{/script?foo=1&bar=2,inline link in pointy braces}.
@node Autolinks
@section Autolinks
With an ampersand: @url{http://example.com/?foo=1&bar=2}
@itemize
@item
In a list?
@item
@url{http://example.com/}
@item
It should.
@end itemize
An e-mail address: @uref{mailto:nobody@@nowhere.net,@verb{!nobody@@nowhere.net!}}
@quotation
Blockquoted: @url{http://example.com/}
@end quotation
Auto-links should not occur here: @verb{!<http://example.com/>!}
@verbatim
or here: <http://example.com/>
@end verbatim
@iftex
@bigskip@hrule@bigskip
@end iftex
@ifnottex
------------------------------------------------------------------------
@end ifnottex
@node Images
@chapter Images
From ``Voyage dans la Lune'' by Georges Melies (1902):
@image{lalune,,,lalune,jpg}
Here is a movie @image{movie,,,movie,jpg} icon.
@iftex
@bigskip@hrule@bigskip
@end iftex
@ifnottex
------------------------------------------------------------------------
@end ifnottex
@node Footnotes
@chapter Footnotes
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].}
@quotation
Notes can go in quotes.@footnote{In quote.}
@end quotation
@enumerate
@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