diff options
-rw-r--r-- | pandoc.cabal | 1 | ||||
-rw-r--r-- | src/Main.hs | 1 | ||||
-rw-r--r-- | src/Text/Pandoc.hs | 2 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/ConTeXt.hs | 225 | ||||
-rw-r--r-- | src/headers/ConTeXtHeader | 54 | ||||
-rw-r--r-- | src/templates/DefaultHeaders.hs | 4 | ||||
-rwxr-xr-x | tests/generate.sh | 1 | ||||
-rw-r--r-- | tests/runtests.pl | 10 | ||||
-rw-r--r-- | tests/tables.context | 135 | ||||
-rw-r--r-- | tests/writer.context | 708 |
10 files changed, 1140 insertions, 1 deletions
diff --git a/pandoc.cabal b/pandoc.cabal index f3d9bbf1c..dbd20342c 100644 --- a/pandoc.cabal +++ b/pandoc.cabal @@ -49,6 +49,7 @@ Exposed-Modules: Text.Pandoc, Text.Pandoc.Writers.Docbook, Text.Pandoc.Writers.HTML, Text.Pandoc.Writers.LaTeX, + Text.Pandoc.Writers.ConTeXt, Text.Pandoc.Writers.Man, Text.Pandoc.Writers.Markdown, Text.Pandoc.Writers.RST, diff --git a/src/Main.hs b/src/Main.hs index 49cc33040..88870b6a4 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -72,6 +72,7 @@ writers = [("native" , (writeDoc, "")) ,("s5" , (writeS5String, defaultS5Header)) ,("docbook" , (writeDocbook, defaultDocbookHeader)) ,("latex" , (writeLaTeX, defaultLaTeXHeader)) + ,("context" , (writeConTeXt, defaultConTeXtHeader)) ,("man" , (writeMan, "")) ,("markdown" , (writeMarkdown, "")) ,("rst" , (writeRST, "")) diff --git a/src/Text/Pandoc.hs b/src/Text/Pandoc.hs index ad24eef4d..fe724987c 100644 --- a/src/Text/Pandoc.hs +++ b/src/Text/Pandoc.hs @@ -67,6 +67,7 @@ module Text.Pandoc , writeMarkdown , writeRST , writeLaTeX + , writeConTeXt , writeHtml , writeHtmlString , writeS5 @@ -92,6 +93,7 @@ import Text.Pandoc.Readers.HTML import Text.Pandoc.Writers.Markdown import Text.Pandoc.Writers.RST import Text.Pandoc.Writers.LaTeX +import Text.Pandoc.Writers.ConTeXt import Text.Pandoc.Writers.HTML import Text.Pandoc.Writers.S5 import Text.Pandoc.Writers.Docbook diff --git a/src/Text/Pandoc/Writers/ConTeXt.hs b/src/Text/Pandoc/Writers/ConTeXt.hs new file mode 100644 index 000000000..dec33c9e0 --- /dev/null +++ b/src/Text/Pandoc/Writers/ConTeXt.hs @@ -0,0 +1,225 @@ +{- +Copyright (C) 2007 John MacFarlane <jgm@berkeley.edu> + +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.ConTeXt + Copyright : Copyright (C) 2006-7 John MacFarlane + License : GNU GPL, version 2 or above + + Maintainer : John MacFarlane <jgm@berkeley.edu> + Stability : alpha + Portability : portable + +Conversion of 'Pandoc' format into ConTeXt. +-} +module Text.Pandoc.Writers.ConTeXt ( + writeConTeXt + ) where +import Text.Pandoc.Definition +import Text.Pandoc.Shared +import Text.Printf ( printf ) +import Data.List ( (\\), intersperse ) +import Control.Monad.State + +type WriterState = Int -- number of next URL reference + +-- | Convert Pandoc to ConTeXt. +writeConTeXt :: WriterOptions -> Pandoc -> String +writeConTeXt options document = + evalState (pandocToConTeXt options document) 1 + +pandocToConTeXt :: WriterOptions -> Pandoc -> State WriterState String +pandocToConTeXt options (Pandoc meta blocks) = do + main <- blockListToConTeXt blocks + let body = writerIncludeBefore options ++ main ++ writerIncludeAfter options + head <- if writerStandalone options + then contextHeader options meta + else return "" + let toc = if writerTableOfContents options + then "\\placecontent\n\n" + else "" + let foot = if writerStandalone options + then "\n\\stoptext\n" + else "" + return $ head ++ toc ++ body ++ foot + +-- | Insert bibliographic information into ConTeXt header. +contextHeader :: WriterOptions -- ^ Options, including ConTeXt header + -> Meta -- ^ Meta with bibliographic information + -> State WriterState String +contextHeader options (Meta title authors date) = do + titletext <- if null title + then return "" + else inlineListToConTeXt title + let authorstext = if null authors + then "" + else if length authors == 1 + then stringToConTeXt $ head authors + else stringToConTeXt $ (joinWithSep ", " $ + init authors) ++ " & " ++ last authors + let datetext = if date == "" + then "" + else stringToConTeXt date + let titleblock = "\\doctitle{" ++ titletext ++ "}\n\ + \ \\author{" ++ authorstext ++ "}\n\ + \ \\date{" ++ datetext ++ "}\n\n" + let setupheads = if (writerNumberSections options) + then "\\setupheads[sectionnumber=yes, style=\\bf]\n" + else "\\setupheads[sectionnumber=no, style=\\bf]\n" + let header = writerHeader options + return $ header ++ setupheads ++ titleblock ++ "\\starttext\n\\maketitle\n\n" + +-- escape things as needed for ConTeXt + +escapeCharForConTeXt :: Char -> String +escapeCharForConTeXt ch = + case ch of + '{' -> "\\letteropenbrace{}" + '}' -> "\\letterclosebrace{}" + '\\' -> "\\letterbackslash{}" + '$' -> "\\$" + '|' -> "\\letterbar{}" + '^' -> "\\letterhat{}" + '%' -> "\\%" + '~' -> "\\lettertilde{}" + '&' -> "\\&" + '#' -> "\\#" + '<' -> "\\letterless{}" + '>' -> "\\lettermore{}" + '_' -> "\\letterunderscore{}" + x -> [x] + +-- | Escape string for ConTeXt +stringToConTeXt :: String -> String +stringToConTeXt = concatMap escapeCharForConTeXt + +-- | Convert Pandoc block element to ConTeXt. +blockToConTeXt :: Block -> State WriterState String +blockToConTeXt Null = return "" +blockToConTeXt (Plain lst) = inlineListToConTeXt lst >>= (return . (++ "\n")) +blockToConTeXt (Para lst) = inlineListToConTeXt lst >>= (return . (++ "\n\n")) +blockToConTeXt (BlockQuote lst) = do + contents <- blockListToConTeXt lst + return $ "\\startnarrower\n" ++ contents ++ "\\stopnarrower\n\n" +blockToConTeXt (CodeBlock str) = + return $ "\\starttyping\n" ++ str ++ "\n\\stoptyping\n" +blockToConTeXt (RawHtml str) = return "" +blockToConTeXt (BulletList lst) = do + contents <- mapM listItemToConTeXt lst + return $ "\\startltxitem\n" ++ concat contents ++ "\\stopltxitem\n" +blockToConTeXt (OrderedList lst) = do + contents <- mapM listItemToConTeXt lst + return $ "\\startltxenum\n" ++ concat contents ++ "\\stopltxenum\n" +blockToConTeXt (DefinitionList lst) = + mapM defListItemToConTeXt lst >>= (return . (++ "\n") . concat) +blockToConTeXt HorizontalRule = return "\\thinrule\n\n" +blockToConTeXt (Header level lst) = do + contents <- inlineListToConTeXt lst + return $ if (level > 0) && (level <= 3) + then "\\" ++ (concat (replicate (level - 1) "sub")) ++ + "section{" ++ contents ++ "}\n\n" + else contents ++ "\n\n" +blockToConTeXt (Table caption aligns widths heads rows) = do + let colWidths = map printDecimal widths + let colDescriptor colWidth alignment = (case alignment of + AlignLeft -> 'l' + AlignRight -> 'r' + AlignCenter -> 'c' + AlignDefault -> 'l'): + "p(" ++ colWidth ++ "\\textwidth)|" + let colDescriptors = "|" ++ (concat $ + zipWith colDescriptor colWidths aligns) + headers <- tableRowToConTeXt heads + captionText <- inlineListToConTeXt caption + let captionText' = if null caption then "none" else captionText + rows' <- mapM tableRowToConTeXt rows + return $ "\\placetable[here]{" ++ captionText' ++ "}\n\\starttable[" ++ + colDescriptors ++ "]\n" ++ "\\HL\n" ++ headers ++ "\\HL\n" ++ + concat rows' ++ "\\HL\n\\stoptable\n\n" + +printDecimal :: Float -> String +printDecimal = printf "%.2f" + +tableRowToConTeXt cols = do + cols' <- mapM blockListToConTeXt cols + return $ "\\NC " ++ (concat $ intersperse "\\NC " cols') ++ "\\NC\\AR\n" + +listItemToConTeXt list = do + contents <- blockListToConTeXt list + return $ "\\item " ++ contents + +defListItemToConTeXt (term, def) = do + term' <- inlineListToConTeXt term + def' <- blockListToConTeXt def + return $ "\\startdescr{" ++ term' ++ "}\n" ++ + def' ++ "\n\\stopdescr\n" + +-- | Convert list of block elements to ConTeXt. +blockListToConTeXt :: [Block] -> State WriterState String +blockListToConTeXt lst = mapM blockToConTeXt lst >>= (return . concat) + +-- | Convert list of inline elements to ConTeXt. +inlineListToConTeXt :: [Inline] -- ^ Inlines to convert + -> State WriterState String +inlineListToConTeXt lst = mapM inlineToConTeXt lst >>= (return . concat) + +isQuoted :: Inline -> Bool +isQuoted (Quoted _ _) = True +isQuoted Apostrophe = True +isQuoted _ = False + +-- | Convert inline element to ConTeXt +inlineToConTeXt :: Inline -- ^ Inline to convert + -> State WriterState String +inlineToConTeXt (Emph lst) = do + contents <- inlineListToConTeXt lst + return $ "{\\em " ++ contents ++ "}" +inlineToConTeXt (Strong lst) = do + contents <- inlineListToConTeXt lst + return $ "{\\bf " ++ contents ++ "}" +inlineToConTeXt (Code str) = return $ "\\type{" ++ str ++ "}" +inlineToConTeXt (Quoted SingleQuote lst) = do + contents <- inlineListToConTeXt lst + return $ "\\quote{" ++ contents ++ "}" +inlineToConTeXt (Quoted DoubleQuote lst) = do + contents <- inlineListToConTeXt lst + return $ "\\quotation{" ++ contents ++ "}" +inlineToConTeXt Apostrophe = return "'" +inlineToConTeXt EmDash = return "---" +inlineToConTeXt EnDash = return "--" +inlineToConTeXt Ellipses = return "\\ldots{}" +inlineToConTeXt (Str str) = return $ stringToConTeXt str +inlineToConTeXt (TeX str) = return str +inlineToConTeXt (HtmlInline str) = return "" +inlineToConTeXt (LineBreak) = return "\\hfil\\break\n" +inlineToConTeXt Space = return " " +inlineToConTeXt (Link text (src, _)) = do + next <- get + put (next + 1) + let ref = show next + label <- inlineListToConTeXt text + return $ "\\useurl[" ++ ref ++ "][" ++ src ++ "][][" ++ label ++ + "]\\from[" ++ ref ++ "]" +inlineToConTeXt (Image alternate (src, tit)) = do + alt <- inlineListToConTeXt alternate + return $ "\\placefigure\n[]\n[fig:" ++ alt ++ "]\n{" ++ + tit ++ "}\n{\\externalfigure[" ++ src ++ "]}" +inlineToConTeXt (Note contents) = do + contents' <- blockListToConTeXt contents + return $ "\\footnote{" ++ contents' ++ "}" + diff --git a/src/headers/ConTeXtHeader b/src/headers/ConTeXtHeader new file mode 100644 index 000000000..7a27b38d8 --- /dev/null +++ b/src/headers/ConTeXtHeader @@ -0,0 +1,54 @@ +\enableregime[utf] % use UTF-8 + +\setupcolors[state=start] +\setupinteraction[state=start, color=middlered] % needed for hyperlinks + +\setuppapersize[letter][letter] % use letter paper +\setuplayout[width=6in, height=9.5in] % page layout +\setuppagenumbering[location={footer,center}, style=bold] % number pages +\setupbodyfont[11pt] % 11pt font +\setupwhitespace[medium] % inter-paragraph spacing + +\setuphead[section][style=\tfc] +\setuphead[subsection][style=\tfb] +\setuphead[subsubsection][style=\bf] + +% define title block commands +\unprotect +\def\doctitle#1{\gdef\@title{#1}} +\def\author#1{\gdef\@author{#1}} +\def\date#1{\gdef\@date{#1}} +\date{\currentdate} % Default to today unless specified otherwise. +\def\maketitle{% + \startalignment[center] + \blank[2*big] + {\tfd \@title} + \blank[3*medium] + {\tfa \@author} + \blank[2*medium] + {\tfa \@date} + \blank[3*medium] + \stopalignment} +\protect + +% define descr (for definition lists) +\definedescription[descr][ + headstyle=bold,style=normal,align=left,location=hanging, + width=broad,margin=1cm] + +% define ltxitem (for bulleted lists) +\defineitemgroup[ltxitem][levels=4] +\setupitemgroup[ltxitem][1][1] +\setupitemgroup[ltxitem][2][2] +\setupitemgroup[ltxitem][3][3] +\setupitemgroup[ltxitem][4][4,packed] + +% define ltxenum (for enumerated lists) +\defineitemgroup[ltxenum][levels=4] +\setupitemgroup[ltxenum][1][n] +\setupitemgroup[ltxenum][2][a] +\setupitemgroup[ltxenum][3][r] +\setupitemgroup[ltxenum][4][A,packed] + +\setupthinrules[width=15em] % width of horizontal rules + diff --git a/src/templates/DefaultHeaders.hs b/src/templates/DefaultHeaders.hs index 7aee8c945..d7815fb8a 100644 --- a/src/templates/DefaultHeaders.hs +++ b/src/templates/DefaultHeaders.hs @@ -1,6 +1,7 @@ -- | Default headers for Pandoc writers. module Text.Pandoc.Writers.DefaultHeaders ( defaultLaTeXHeader, + defaultConTeXtHeader, defaultDocbookHeader, defaultS5Header, defaultRTFHeader @@ -10,6 +11,9 @@ import Text.Pandoc.Writers.S5 defaultLaTeXHeader :: String defaultLaTeXHeader = "@LaTeXHeader@" +defaultConTeXtHeader :: String +defaultConTeXtHeader = "@ConTeXtHeader@" + defaultDocbookHeader :: String defaultDocbookHeader = "@DocbookHeader@" diff --git a/tests/generate.sh b/tests/generate.sh index c2e5eff0f..15e931b6c 100755 --- a/tests/generate.sh +++ b/tests/generate.sh @@ -8,4 +8,5 @@ ../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 +sed -e '/^, Header 1 \[Str "LaTeX"\]/,/^, HorizontalRule/d' testsuite.native | ../pandoc -r native -w context -s > writer.context diff --git a/tests/runtests.pl b/tests/runtests.pl index af0f0bc16..06e7a1b3e 100644 --- a/tests/runtests.pl +++ b/tests/runtests.pl @@ -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 and s5 handled separately +my @writeformats = ("html", "latex", "rst", "rtf", "markdown", "man", "native"); # docbook, context, and s5 handled separately my @readformats = ("latex", "native"); # handle html,markdown & rst separately my $source = "testsuite.native"; @@ -61,6 +61,14 @@ test_results("docbook writer", "tmp.docbook", "writer.docbook"); print " docbook tables..."; test_results("docbook tables", "tmp.docbook", "tables.docbook"); +print "Testing context writer..."; +# remove LaTeX tests, as this produces invalid docbook... +`sed -e '/^, Header 1 \\[Str "LaTeX"\\]/,/^, HorizontalRule/d' testsuite.native | $script -r native -w context -s > tmp.context`; +test_results("context writer", "tmp.context", "writer.context"); +`$script -r native -w context tables.native > tmp.context`; +print " context tables..."; +test_results("context tables", "tmp.context", "tables.context"); + print "Testing s5 writer (basic)..."; `$script -r native -w s5 -s s5.native > tmp.html`; test_results("s5 writer (basic)", "tmp.html", "s5.basic.html"); diff --git a/tests/tables.context b/tests/tables.context new file mode 100644 index 000000000..cb6e9ccd1 --- /dev/null +++ b/tests/tables.context @@ -0,0 +1,135 @@ +Simple table with caption: + +\placetable[here]{Demonstration of simple table syntax.} +\starttable[|rp(0.15\textwidth)|lp(0.09\textwidth)|cp(0.16\textwidth)|lp(0.13\textwidth)|] +\HL +\NC Right +\NC Left +\NC Center +\NC Default +\NC\AR +\HL +\NC 12 +\NC 12 +\NC 12 +\NC 12 +\NC\AR +\NC 123 +\NC 123 +\NC 123 +\NC 123 +\NC\AR +\NC 1 +\NC 1 +\NC 1 +\NC 1 +\NC\AR +\HL +\stoptable + +Simple table without caption: + +\placetable[here]{none} +\starttable[|rp(0.15\textwidth)|lp(0.09\textwidth)|cp(0.16\textwidth)|lp(0.13\textwidth)|] +\HL +\NC Right +\NC Left +\NC Center +\NC Default +\NC\AR +\HL +\NC 12 +\NC 12 +\NC 12 +\NC 12 +\NC\AR +\NC 123 +\NC 123 +\NC 123 +\NC 123 +\NC\AR +\NC 1 +\NC 1 +\NC 1 +\NC 1 +\NC\AR +\HL +\stoptable + +Simple table indented two spaces: + +\placetable[here]{Demonstration of simple table syntax.} +\starttable[|rp(0.15\textwidth)|lp(0.09\textwidth)|cp(0.16\textwidth)|lp(0.13\textwidth)|] +\HL +\NC Right +\NC Left +\NC Center +\NC Default +\NC\AR +\HL +\NC 12 +\NC 12 +\NC 12 +\NC 12 +\NC\AR +\NC 123 +\NC 123 +\NC 123 +\NC 123 +\NC\AR +\NC 1 +\NC 1 +\NC 1 +\NC 1 +\NC\AR +\HL +\stoptable + +Multiline table with caption: + +\placetable[here]{Here's the caption. It may span multiple lines.} +\starttable[|cp(0.15\textwidth)|lp(0.14\textwidth)|rp(0.16\textwidth)|lp(0.34\textwidth)|] +\HL +\NC Centered Header +\NC Left Aligned +\NC Right Aligned +\NC Default aligned +\NC\AR +\HL +\NC First +\NC row +\NC 12.0 +\NC Example of a row that spans multiple lines. +\NC\AR +\NC Second +\NC row +\NC 5.0 +\NC Here's another one. Note the blank line between rows. +\NC\AR +\HL +\stoptable + +Multiline table without caption: + +\placetable[here]{none} +\starttable[|cp(0.15\textwidth)|lp(0.14\textwidth)|rp(0.16\textwidth)|lp(0.34\textwidth)|] +\HL +\NC Centered Header +\NC Left Aligned +\NC Right Aligned +\NC Default aligned +\NC\AR +\HL +\NC First +\NC row +\NC 12.0 +\NC Example of a row that spans multiple lines. +\NC\AR +\NC Second +\NC row +\NC 5.0 +\NC Here's another one. Note the blank line between rows. +\NC\AR +\HL +\stoptable + diff --git a/tests/writer.context b/tests/writer.context new file mode 100644 index 000000000..4176965e9 --- /dev/null +++ b/tests/writer.context @@ -0,0 +1,708 @@ +\enableregime[utf] % use UTF-8 + +\setupcolors[state=start] +\setupinteraction[state=start, color=middlered] % needed for hyperlinks + +\setuppapersize[letter][letter] % use letter paper +\setuplayout[width=6in, height=9.5in] % page layout +\setuppagenumbering[location={footer,center}, style=bold] % number pages +\setupbodyfont[11pt] % 11pt font +\setupwhitespace[medium] % inter-paragraph spacing + +\setuphead[section][style=\tfc] +\setuphead[subsection][style=\tfb] +\setuphead[subsubsection][style=\bf] + +% define title block commands +\unprotect +\def\doctitle#1{\gdef\@title{#1}} +\def\author#1{\gdef\@author{#1}} +\def\date#1{\gdef\@date{#1}} +\date{\currentdate} % Default to today unless specified otherwise. +\def\maketitle{% + \startalignment[center] + \blank[2*big] + {\tfd \@title} + \blank[3*medium] + {\tfa \@author} + \blank[2*medium] + {\tfa \@date} + \blank[3*medium] + \stopalignment} +\protect + +% define descr (for definition lists) +\definedescription[descr][ + headstyle=bold,style=normal,align=left,location=hanging, + width=broad,margin=1cm] + +% define ltxitem (for bulleted lists) +\defineitemgroup[ltxitem][levels=4] +\setupitemgroup[ltxitem][1][1] +\setupitemgroup[ltxitem][2][2] +\setupitemgroup[ltxitem][3][3] +\setupitemgroup[ltxitem][4][4,packed] + +% define ltxenum (for enumerated lists) +\defineitemgroup[ltxenum][levels=4] +\setupitemgroup[ltxenum][1][n] +\setupitemgroup[ltxenum][2][a] +\setupitemgroup[ltxenum][3][r] +\setupitemgroup[ltxenum][4][A,packed] + +\setupthinrules[width=15em] % width of horizontal rules + +\setupheads[sectionnumber=no, style=\bf] +\doctitle{Pandoc Test Suite} + \author{John MacFarlane \& Anonymous} + \date{July 17, 2006} + +\starttext +\maketitle + +This is a set of tests for pandoc. Most of them are adapted from John Gruber's markdown test suite. + +\thinrule + +\section{Headers} + +\subsection{Level 2 with an \useurl[1][/url][][embedded link]\from[1]} + +\subsubsection{Level 3 with {\em emphasis}} + +Level 4 + +Level 5 + +\section{Level 1} + +\subsection{Level 2 with {\em emphasis}} + +\subsubsection{Level 3} + +with no blank line + +\subsection{Level 2} + +with no blank line + +\thinrule + +\section{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\hfil\break +here. + +\thinrule + +\section{Block Quotes} + +E-mail style: + +\startnarrower +This is a block quote. It is pretty short. + +\stopnarrower + +\startnarrower +Code in a block quote: + +\starttyping +sub status { + print "working"; +} +\stoptyping +A list: + +\startltxenum +\item item one +\item item two +\stopltxenum +Nested block quotes: + +\startnarrower +nested + +\stopnarrower + +\startnarrower +nested + +\stopnarrower + +\stopnarrower + +This should not be a block quote: 2 \lettermore{} 1. + +Box-style: + +\startnarrower +Example: + +\starttyping +sub status { + print "working"; +} +\stoptyping +\stopnarrower + +\startnarrower +\startltxenum +\item do laundry +\item take out the trash +\stopltxenum +\stopnarrower + +Here's a nested one: + +\startnarrower +Joe said: + +\startnarrower +Don't quote me. + +\stopnarrower + +\stopnarrower + +And a following paragraph. + +\thinrule + +\section{Code Blocks} + +Code: + +\starttyping +---- (should be four hyphens) + +sub status { + print "working"; +} + +this code block is indented by one tab +\stoptyping +And: + +\starttyping + this code block is indented by two tabs + +These should not be escaped: \$ \\ \> \[ \{ +\stoptyping +\thinrule + +\section{Lists} + +\subsection{Unordered} + +Asterisks tight: + +\startltxitem +\item asterisk 1 +\item asterisk 2 +\item asterisk 3 +\stopltxitem +Asterisks loose: + +\startltxitem +\item asterisk 1 + +\item asterisk 2 + +\item asterisk 3 + +\stopltxitem +Pluses tight: + +\startltxitem +\item Plus 1 +\item Plus 2 +\item Plus 3 +\stopltxitem +Pluses loose: + +\startltxitem +\item Plus 1 + +\item Plus 2 + +\item Plus 3 + +\stopltxitem +Minuses tight: + +\startltxitem +\item Minus 1 +\item Minus 2 +\item Minus 3 +\stopltxitem +Minuses loose: + +\startltxitem +\item Minus 1 + +\item Minus 2 + +\item Minus 3 + +\stopltxitem +\subsection{Ordered} + +Tight: + +\startltxenum +\item First +\item Second +\item Third +\stopltxenum +and: + +\startltxenum +\item One +\item Two +\item Three +\stopltxenum +Loose using tabs: + +\startltxenum +\item First + +\item Second + +\item Third + +\stopltxenum +and using spaces: + +\startltxenum +\item One + +\item Two + +\item Three + +\stopltxenum +Multiple paragraphs: + +\startltxenum +\item Item 1, graf one. + +Item 1. graf two. The quick brown fox jumped over the lazy dog's back. + +\item Item 2. + +\item Item 3. + +\stopltxenum +\subsection{Nested} + +\startltxitem +\item Tab +\startltxitem +\item Tab +\startltxitem +\item Tab +\stopltxitem +\stopltxitem +\stopltxitem +Here's another: + +\startltxenum +\item First +\item Second: +\startltxitem +\item Fee +\item Fie +\item Foe +\stopltxitem +\item Third +\stopltxenum +Same thing but with paragraphs: + +\startltxenum +\item First + +\item Second: + +\startltxitem +\item Fee +\item Fie +\item Foe +\stopltxitem +\item Third + +\stopltxenum +\subsection{Tabs and spaces} + +\startltxitem +\item this is a list item indented with tabs + +\item this is a list item indented with spaces + +\startltxitem +\item this is an example list item indented with tabs + +\item this is an example list item indented with spaces + +\stopltxitem +\stopltxitem +\thinrule + +\section{Definition Lists} + +Tight using spaces: + +\startdescr{apple} +red fruit + +\stopdescr +\startdescr{orange} +orange fruit + +\stopdescr +\startdescr{banana} +yellow fruit + +\stopdescr + +Tight using tabs: + +\startdescr{apple} +red fruit + +\stopdescr +\startdescr{orange} +orange fruit + +\stopdescr +\startdescr{banana} +yellow fruit + +\stopdescr + +Loose: + +\startdescr{apple} +red fruit + + +\stopdescr +\startdescr{orange} +orange fruit + + +\stopdescr +\startdescr{banana} +yellow fruit + + +\stopdescr + +Multiple blocks with italics: + +\startdescr{{\em apple}} +red fruit + +contains seeds, crisp, pleasant to taste + + +\stopdescr +\startdescr{{\em orange}} +orange fruit + +\starttyping +{ orange code block } +\stoptyping +\startnarrower +orange block quote + +\stopnarrower + + +\stopdescr + +\section{HTML Blocks} + +Simple block on one line: + +foo +And nested without indentation: + +foo +bar +Interpreted markdown in a table: + +This is {\em emphasized} +And this is {\bf strong} +Here's a simple block: + +foo +This should be a code block, though: + +\starttyping +<div> + foo +</div> +\stoptyping +As should this: + +\starttyping +<div>foo</div> +\stoptyping +Now, nested: + +foo +This should just be an HTML comment: + +Multiline: + +Code block: + +\starttyping +<!-- Comment --> +\stoptyping +Just plain comment, with trailing spaces on the line: + +Code: + +\starttyping +<hr /> +\stoptyping +Hr's: + +\thinrule + +\section{Inline Markup} + +This is {\em emphasized}, and so {\em is this}. + +This is {\bf strong}, and so {\bf is this}. + +An {\em \useurl[2][/url][][emphasized link]\from[2]}. + +{\bf {\em This is strong and em.}} + +So is {\bf {\em this}} word. + +{\bf {\em This is strong and em.}} + +So is {\bf {\em this}} word. + +This is code: \type{>}, \type{$}, \type{\}, \type{\$}, \type{<html>}. + +\thinrule + +\section{Smart quotes, ellipses, dashes} + +\quotation{Hello,} said the spider. \quotation{\quote{Shelob} is my name.} + +\quote{A}, \quote{B}, and \quote{C} are letters. + +\quote{Oak,} \quote{elm,} and \quote{beech} are names of trees. So is \quote{pine.} + +\quote{He said, \quotation{I want to go.}} Were you alive in the 70's? + +Here is some quoted \quote{\type{code}} and a \quotation{\useurl[3][http://example.com/?foo=1&bar=2][][quoted link]\from[3]}. + +Some dashes: one---two---three---four---five. + +Dashes between numbers: 5--7, 255--66, 1987--1999. + +Ellipses\ldots{}and\ldots{}and\ldots{}. + +\thinrule + +\section{Special Characters} + +Here is some unicode: + +\startltxitem +\item I hat: Î +\item o umlaut: ö +\item section: § +\item set membership: ∈ +\item copyright: © +\stopltxitem +AT\&T has an ampersand in their name. + +AT\&T is another way to write it. + +This \& that. + +4 \letterless{} 5. + +6 \lettermore{} 5. + +Backslash: \letterbackslash{} + +Backtick: ` + +Asterisk: * + +Underscore: \letterunderscore{} + +Left brace: \letteropenbrace{} + +Right brace: \letterclosebrace{} + +Left bracket: [ + +Right bracket: ] + +Left paren: ( + +Right paren: ) + +Greater-than: \lettermore{} + +Hash: \# + +Period: . + +Bang: ! + +Plus: + + +Minus: - + +\thinrule + +\section{Links} + +\subsection{Explicit} + +Just a \useurl[4][/url/][][URL]\from[4]. + +\useurl[5][/url/][][URL and title]\from[5]. + +\useurl[6][/url/][][URL and title]\from[6]. + +\useurl[7][/url/][][URL and title]\from[7]. + +\useurl[8][/url/][][URL and title]\from[8] + +\useurl[9][/url/][][URL and title]\from[9] + +\useurl[10][/url/with_underscore][][with\letterunderscore{}underscore]\from[10] + +\useurl[11][mailto:nobody@nowhere.net][][Email link]\from[11] + +\useurl[12][][][Empty]\from[12]. + +\subsection{Reference} + +Foo \useurl[13][/url/][][bar]\from[13]. + +Foo \useurl[14][/url/][][bar]\from[14]. + +Foo \useurl[15][/url/][][bar]\from[15]. + +With \useurl[16][/url/][][embedded [brackets]]\from[16]. + +\useurl[17][/url/][][b]\from[17] by itself should be a link. + +Indented \useurl[18][/url][][once]\from[18]. + +Indented \useurl[19][/url][][twice]\from[19]. + +Indented \useurl[20][/url][][thrice]\from[20]. + +This should [not][] be a link. + +\starttyping +[not]: /url +\stoptyping +Foo \useurl[21][/url/][][bar]\from[21]. + +Foo \useurl[22][/url/][][biz]\from[22]. + +\subsection{With ampersands} + +Here's a \useurl[23][http://example.com/?foo=1&bar=2][][link with an ampersand in the URL]\from[23]. + +Here's a link with an amersand in the link text: \useurl[24][http://att.com/][][AT\&T]\from[24]. + +Here's an \useurl[25][/script?foo=1&bar=2][][inline link]\from[25]. + +Here's an \useurl[26][/script?foo=1&bar=2][][inline link in pointy braces]\from[26]. + +\subsection{Autolinks} + +With an ampersand: \useurl[27][http://example.com/?foo=1&bar=2][][http://example.com/?foo=1\&bar=2]\from[27] + +\startltxitem +\item In a list? +\item \useurl[28][http://example.com/][][http://example.com/]\from[28] +\item It should. +\stopltxitem +An e-mail address: \useurl[29][mailto:nobody@nowhere.net][][nobody@nowhere.net]\from[29] + +\startnarrower +Blockquoted: \useurl[30][http://example.com/][][http://example.com/]\from[30] + +\stopnarrower + +Auto-links should not occur here: \type{<http://example.com/>} + +\starttyping +or here: <http://example.com/> +\stoptyping +\thinrule + +\section{Images} + +From \quotation{Voyage dans la Lune} by Georges Melies (1902): + +\placefigure +[] +[fig:lalune] +{Voyage dans la Lune} +{\externalfigure[lalune.jpg]} + +Here is a movie \placefigure +[] +[fig:movie] +{} +{\externalfigure[movie.jpg]} icon. + +\thinrule + +\section{Footnotes} + +Here is a footnote reference,\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). + +\starttyping + { <code> } +\stoptyping +If you want, you can indent every line, but you can also be lazy and just indent the first line of each block. + +} This should {\em not} be a footnote reference, because it contains a space.[\letterhat{}my note] Here is an inline note.\footnote{This is {\em easier} to type. Inline notes may contain \useurl[31][http://google.com][][links]\from[31] and \type{]} verbatim characters, as well as [bracketed text]. + +} + +\startnarrower +Notes can go in quotes.\footnote{In quote. + +} + +\stopnarrower + +\startltxenum +\item And in list items.\footnote{In list. + +} +\stopltxenum +This paragraph should not be part of the note, as it is not indented. + + +\stoptext |