diff --git a/AUTHORS.md b/AUTHORS.md index 4cf2ac2d0c35..9d7e22e78d3e 100644 --- a/AUTHORS.md +++ b/AUTHORS.md @@ -35,6 +35,7 @@ - Brent Yorgey - Brian Leung - Bryan O'Sullivan +- Caleb Maclennan - Caleb McDaniel - Caleb Mclennan - Calvin Beck diff --git a/MANUAL.txt b/MANUAL.txt index e468c86da78f..f78a921c2326 100644 --- a/MANUAL.txt +++ b/MANUAL.txt @@ -327,6 +327,7 @@ header when requesting a document from a URL: - `rtf` ([Rich Text Format]) - `texinfo` ([GNU Texinfo]) - `textile` ([Textile]) + - `sile` ([SILE]) - `slideous` ([Slideous] HTML and JavaScript slide show) - `slidy` ([Slidy] HTML and JavaScript slide show) - `dzslides` ([DZSlides] HTML5 + JavaScript slide show), @@ -448,6 +449,7 @@ header when requesting a document from a URL: [MultiMarkdown]: https://fletcherpenney.net/multimarkdown/ [reStructuredText]: https://docutils.sourceforge.io/docs/ref/rst/introduction.html [S5]: https://meyerweb.com/eric/tools/s5/ +[SILE]: https://www.sile-typesetter.org/ [Slidy]: https://www.w3.org/Talks/Tools/Slidy2/ [Slideous]: https://goessner.net/articles/slideous/ [HTML]: https://www.w3.org/html/ @@ -913,7 +915,7 @@ header when requesting a document from a URL: `--no-check-certificate` -: Disable the certificate verification to allow access to +: Disable the certificate verification to allow access to unsecure HTTP resources (for example when the certificate is no longer valid or self signed). @@ -976,7 +978,7 @@ header when requesting a document from a URL: `--top-level-division=[default|section|chapter|part]` -: Treat top-level headings as the given division type in LaTeX, ConTeXt, +: Treat top-level headings as the given division type in LaTeX, ConTeXt, SILE, DocBook, and TEI output. The hierarchy order is part, chapter, then section; all headings are shifted such that the top-level heading becomes the specified type. The default behavior is to determine the best division type via @@ -989,7 +991,7 @@ header when requesting a document from a URL: `-N`, `--number-sections` -: Number section headings in LaTeX, ConTeXt, HTML, Docx, or EPUB output. +: Number section headings in LaTeX, ConTeXt, SILE, HTML, Docx, or EPUB output. By default, sections are not numbered. Sections with class `unnumbered` will never be numbered, even if `--number-sections` is specified. @@ -2067,7 +2069,7 @@ Currently the following pipes are predefined: `title`, `author`, `date` : allow identification of basic aspects of the document. Included - in PDF metadata through LaTeX and ConTeXt. These can be set + in PDF metadata through LaTeX, ConTeXt, and SILE. These can be set through a [pandoc title block][Extension: `pandoc_title_block`], which allows for multiple authors, or through a [YAML metadata block][Extension: `yaml_metadata_block`]: @@ -2085,12 +2087,12 @@ Currently the following pipes are predefined: on `title`, `author`, and `date`.) `subtitle` -: document subtitle, included in HTML, EPUB, LaTeX, ConTeXt, and docx - documents +: document subtitle, included in HTML, EPUB, LaTeX, ConTeXt, SILE, + and docx documents `abstract` -: document summary, included in LaTeX, ConTeXt, AsciiDoc, and docx - documents +: document summary, included in LaTeX, ConTeXt, AsciiDoc, + and docx documents `keywords` : list of keywords to be included in HTML, PDF, ODT, pptx, docx @@ -2106,6 +2108,9 @@ Currently the following pipes are predefined: `category` : document category, included in docx and pptx metadata +`rights` +: rights string, included in SILE and EPUB metadata + Additionally, any root-level string metadata, not included in ODT, docx or pptx metadata is added as a *custom property*. @@ -2135,7 +2140,8 @@ ODT or pptx. tags (following the [BCP 47] standard), such as `en` or `en-GB`. The [Language subtag lookup] tool can look up or verify these tags. This affects most formats, and controls hyphenation in PDF output - when using LaTeX (through [`babel`] and [`polyglossia`]) or ConTeXt. + when using LaTeX (through [`babel`] and [`polyglossia`]), ConTeXt, + or SILE. Use native pandoc [Divs and Spans] with the `lang` attribute to switch the language: @@ -2573,6 +2579,33 @@ Pandoc uses these variables when [creating a PDF] with ConTeXt. [`setupinterlinespace`]: https://wiki.contextgarden.net/Command/setupinterlinespace [`setuppagenumbering`]: https://wiki.contextgarden.net/Command/setuppagenumbering +### Variables for SILE + +The following variables are placed appropriately in standalone SILE documents. + +`classoption` +: options for document class; repeat for multiple options: + + --- + classoption: + - layout: yoko + ... + +`documentclass` +: document class: usually one of the standard classes, [`plain`], or [`book`]. + +`fontsize` +: font size for body text (e.g. `10pt`, `12pt`) + +`links-as-notes` +: causes links to be printed as footnotes + +`mainfont`, `sansfont`, `monofont` +: font families: take the name of any system font + +`papersize` +: paper size, e.g. `letter`, `a4` + ### Variables for `wkhtmltopdf` Pandoc uses these variables when [creating a PDF] with [`wkhtmltopdf`]. @@ -2800,7 +2833,7 @@ another. A link to this section, for example, might look like this: [heading identifiers](#heading-identifiers-in-html-latex-and-context). Note, however, that this method of providing links to sections works -only in HTML, LaTeX, and ConTeXt formats. +only in HTML, LaTeX, ConTeXt, and SILE formats. If the `--section-divs` option is specified, then each section will be wrapped in a `section` (or a `div`, if `html4` was specified), @@ -3119,7 +3152,7 @@ Note that although this syntax allows assignment of classes and key/value attributes, writers generally don't use all of this information. Identifiers, classes, and key/value attributes are used in HTML and HTML-based formats such as EPUB and slidy. Identifiers are used for labels and link anchors in the -LaTeX, ConTeXt, Textile, Jira markup, and AsciiDoc writers. +LaTeX, ConTeXt, SILE, Textile, Jira markup, and AsciiDoc writers. Headings with the class `unnumbered` will not be numbered, even if `--number-sections` is specified. A single hyphen (`-`) in an attribute @@ -3135,7 +3168,7 @@ is just the same as If the `unlisted` class is present in addition to `unnumbered`, the heading will not be included in a table of contents. (Currently this feature is only implemented for certain -formats: those based on LaTeX and HTML, PowerPoint, and RTF.) +formats: those based on LaTeX, SILE, HTML, PowerPoint, and RTF.) #### Extension: `implicit_header_references` #### @@ -3292,7 +3325,7 @@ this syntax: Here `mycode` is an identifier, `haskell` and `numberLines` are classes, and `startFrom` is an attribute with value `100`. Some output formats can use this information to do syntax highlighting. Currently, the only output formats -that uses this information are HTML, LaTeX, Docx, Ms, and PowerPoint. If +that uses this information are HTML, LaTeX, SILE, Docx, Ms, and PowerPoint. If highlighting is supported for your output format and language, then the code block above will appear highlighted, with numbered lines. (To see which languages are supported, type `pandoc --list-highlight-languages`.) Otherwise, @@ -4580,7 +4613,7 @@ or [Introduction]: #introduction Internal links are currently supported for HTML formats (including -HTML slide shows and EPUB), LaTeX, and ConTeXt. +HTML slide shows and EPUB), LaTeX, ConTeXt, and SILE. ## Images @@ -4657,9 +4690,10 @@ For example: (If you're using a custom template, you need to configure `graphicx` as in the default template.) - ConTeXt: `\externalfigure[file.jpg][width=0.5\textwidth]` + - SILE: `\img[src=file.jpg][width=50%lw]` - Some output formats have a notion of a class ([ConTeXt](https://wiki.contextgarden.net/Using_Graphics#Multiple_Image_Settings)) - or a unique identifier (LaTeX `\caption`), or both (HTML). + or a unique identifier (LaTeX `\caption`), or both (HTML, SILE). - When no `width` or `height` attributes are specified, the fallback is to look at the image resolution and the dpi metadata embedded in the image file. diff --git a/data/templates/default.sile b/data/templates/default.sile new file mode 100644 index 000000000000..22f7c5748ea8 --- /dev/null +++ b/data/templates/default.sile @@ -0,0 +1,59 @@ +\begin[$if(papersize)$papersize=$papersize$,$endif$class=$documentclass$$if(classoptions)$,$classoptions$$endif$]{document} +\script[src=packages/pandoc] +$if(lang)$ +\language[main=$lang$] +\font[language=$lang$] +$endif$ +$if(langscript)$ +\font[script=$langscript$] +$endif$ +$if(mainfont)$ +\font[family=$mainfont$] +$endif$ +$if(fontsize)$ +\font[size=$fontsize$] +$endif$ +\begin{script} +$if(links-as-notes)$ +SILE.registerCommand("href", function(options, content) + SILE.call("url", options, content) + SILE.call("footnote", options, content) +end) +$else$ +SILE.registerCommand("href", function(options, content) + SILE.call("url", options, content) +end) +$endif$ +\end{script} +$for(include)$ +\script[src=$include$] +$endfor$ +$for(script)$ +\script[src=$script$] +$endfor$ +\set[parameter=linebreak.emergencyStretch,value=1em] +$if(sansfont)$ +\define[command=book:chapterfont]{\font[family=$sansfont$,weight=800,size=20pt]{\process}} +\define[command=book:sectionfont]{\font[family=$sansfont$,weight=800]{\process}} +$endif$ +$if(monofont)$ +\define[command=verbatim:font]{\font[family=$monofont$]} +$endif$ +$if(title-meta)$ +\define[command=title]{$title-meta$} +$endif$ +$if(author-meta)$ +\define[command=author]{$author-meta$} +$endif$ +$if(subtitle-meta)$ +\define[command=subtitle]{$subtitle-meta$} +$endif$ +$if(rights-meta)$ +\define[command=rights]{$title-rights$} +$endif$ +$body$ +$for(include-after)$ +$include-after$ +\script[src=$include-after$] +$endfor$ +\end{document} diff --git a/pandoc.cabal b/pandoc.cabal index ca4e9174c7b9..1fccf445bb09 100644 --- a/pandoc.cabal +++ b/pandoc.cabal @@ -23,7 +23,7 @@ description: Pandoc is a Haskell library for converting from one markup OPML, Emacs Org-Mode, Emacs Muse, txt2tags, ipynb (Jupyter notebooks), Vimwiki, Word Docx, ODT, EPUB, FictionBook2, roff man, Textile, and CSV, and it can write Markdown, - reStructuredText, XHTML, HTML 5, LaTeX, ConTeXt, DocBook, + reStructuredText, XHTML, HTML 5, LaTeX, ConTeXt, SILE, DocBook, JATS, OPML, TEI, OpenDocument, ODT, Word docx, PowerPoint pptx, RTF, MediaWiki, DokuWiki, XWiki, ZimWiki, Textile, Jira, roff man, roff ms, plain text, @@ -56,6 +56,7 @@ data-files: data/templates/default.opml data/templates/default.latex data/templates/default.context + data/templates/default.sile data/templates/default.texinfo data/templates/default.jira data/templates/default.man @@ -538,6 +539,7 @@ library Text.Pandoc.Writers.Jira, Text.Pandoc.Writers.LaTeX, Text.Pandoc.Writers.ConTeXt, + Text.Pandoc.Writers.SILE, Text.Pandoc.Writers.OpenDocument, Text.Pandoc.Writers.Texinfo, Text.Pandoc.Writers.Man, @@ -825,6 +827,7 @@ test-suite test-pandoc Tests.Readers.DokuWiki Tests.Writers.Native Tests.Writers.ConTeXt + Tests.Writers.SILE Tests.Writers.Docbook Tests.Writers.HTML Tests.Writers.JATS @@ -836,6 +839,7 @@ test-suite test-pandoc Tests.Writers.LaTeX Tests.Writers.Docx Tests.Writers.RST + Tests.Writers.SILE Tests.Writers.TEI Tests.Writers.Muse Tests.Writers.FB2 diff --git a/src/Text/Pandoc/App/FormatHeuristics.hs b/src/Text/Pandoc/App/FormatHeuristics.hs index 155b7e586965..0154edbc419a 100644 --- a/src/Text/Pandoc/App/FormatHeuristics.hs +++ b/src/Text/Pandoc/App/FormatHeuristics.hs @@ -61,6 +61,7 @@ formatFromFilePath x = ".rst" -> Just "rst" ".rtf" -> Just "rtf" ".s5" -> Just "s5" + ".sil" -> Just "sile" ".t2t" -> Just "t2t" ".tei" -> Just "tei" ".tei.xml" -> Just "tei" diff --git a/src/Text/Pandoc/Extensions.hs b/src/Text/Pandoc/Extensions.hs index 6415bdc8902b..de54c6253b95 100644 --- a/src/Text/Pandoc/Extensions.hs +++ b/src/Text/Pandoc/Extensions.hs @@ -393,6 +393,9 @@ getDefaultExtensions "epub" = extensionsFromList Ext_epub_html_exts] getDefaultExtensions "epub2" = getDefaultExtensions "epub" getDefaultExtensions "epub3" = getDefaultExtensions "epub" +getDefaultExtensions "sile" = extensionsFromList + [Ext_smart, + Ext_auto_identifiers] getDefaultExtensions "latex" = extensionsFromList [Ext_smart, Ext_latex_macros, diff --git a/src/Text/Pandoc/Writers.hs b/src/Text/Pandoc/Writers.hs index 0654c2d8548e..5940fc63a13a 100644 --- a/src/Text/Pandoc/Writers.hs +++ b/src/Text/Pandoc/Writers.hs @@ -63,6 +63,7 @@ module Text.Pandoc.Writers , writeRTF , writeRevealJs , writeS5 + , writeSILE , writeSlideous , writeSlidy , writeTEI @@ -114,6 +115,7 @@ import Text.Pandoc.Writers.Org import Text.Pandoc.Writers.Powerpoint import Text.Pandoc.Writers.RST import Text.Pandoc.Writers.RTF +import Text.Pandoc.Writers.SILE import Text.Pandoc.Writers.TEI import Text.Pandoc.Writers.Texinfo import Text.Pandoc.Writers.Textile @@ -159,6 +161,7 @@ writers = [ ,("latex" , TextWriter writeLaTeX) ,("beamer" , TextWriter writeBeamer) ,("context" , TextWriter writeConTeXt) + ,("sile" , TextWriter writeSILE) ,("texinfo" , TextWriter writeTexinfo) ,("man" , TextWriter writeMan) ,("ms" , TextWriter writeMs) diff --git a/src/Text/Pandoc/Writers/SILE.hs b/src/Text/Pandoc/Writers/SILE.hs new file mode 100644 index 000000000000..65924c4dce10 --- /dev/null +++ b/src/Text/Pandoc/Writers/SILE.hs @@ -0,0 +1,500 @@ +{-# LANGUAGE NoImplicitPrelude #-} +{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE PatternGuards #-} +{-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE ViewPatterns #-} +{- | + Module : Text.Pandoc.Writers.SILE + Copyright : Copyright (C) 2015-2020 Caleb Maclennan + License : GNU GPL, version 2 or above + + Maintainer : Caleb Maclennan + Stability : alpha + Portability : portable + +Conversion of 'Pandoc' format into SILE. +-} +module Text.Pandoc.Writers.SILE ( + writeSILE + ) where +import Prelude +import Control.Monad.State.Strict +import Data.Char (isAscii, isDigit, isLetter, isPunctuation, ord) +import Data.List (foldl', intersperse) +import Data.Text (Text) +import qualified Data.Text as T +import Network.URI (unEscapeString) +import Text.DocTemplates (FromContext(lookupContext), renderTemplate) +import Text.Pandoc.Class (PandocMonad, report) -- , toLang) +import Text.Pandoc.Definition +import Text.Pandoc.Logging +import Text.Pandoc.Options +import Text.DocLayout +import Text.Pandoc.Shared +import Text.Pandoc.Walk +import Text.Pandoc.Writers.Shared +import Text.Printf (printf) + +data WriterState = + WriterState { + stOLLevel :: Int -- level of ordered list nesting + , stOptions :: WriterOptions -- writer options, so they don't have to be parameter + , stHasChapters :: Bool -- true if document has chapters + , stEmptyLine :: Bool -- true if no content on line + } + +startingState :: WriterOptions -> WriterState +startingState options = WriterState { + stOLLevel = 1 + , stOptions = options + , stHasChapters = case writerTopLevelDivision options of + TopLevelPart -> True + TopLevelChapter -> True + _ -> False + , stEmptyLine = True } + +-- | Convert Pandoc to SILE. +writeSILE :: PandocMonad m => WriterOptions -> Pandoc -> m Text +writeSILE options document = + evalStateT (pandocToSILE options document) $ + startingState options + +type LW m = StateT WriterState m + +pandocToSILE :: PandocMonad m + => WriterOptions -> Pandoc -> LW m Text +pandocToSILE options (Pandoc meta blocks) = do + let blocks' = blocks + let colwidth = if writerWrapText options == WrapAuto + then Just $ writerColumns options + else Nothing + metadata <- metaToContext options + blockListToSILE + (fmap chomp . inlineListToSILE) + meta + let chaptersClasses = ["book","jbook","markdown","bible","triglot","docbook"] + let documentClass = + case lookupContext "documentclass" (writerVariables options) `mplus` + (stringify <$> lookupMeta "documentclass" meta) of + Just x -> x + Nothing -> case writerTopLevelDivision options of + TopLevelPart -> "book" + TopLevelChapter -> "book" + _ -> "plain" + when (documentClass `elem` chaptersClasses) $ + modify $ \s -> s{ stHasChapters = True } + main <- blockListToSILE blocks' + st <- get + titleMeta <- stringToSILE TextString $ stringify $ docTitle meta + authorsMeta <- mapM (stringToSILE TextString . stringify) $ docAuthors meta + + let context = defField "toc" (writerTableOfContents options) $ + defField "toc-depth" (tshow + (writerTOCDepth options - + if stHasChapters st + then 1 + else 0)) $ + defField "body" main $ + defField "title-meta" titleMeta $ + defField "author-meta" + (T.intercalate "; " authorsMeta) $ + defField "documentclass" documentClass $ + defField "numbersections" (writerNumberSections options) $ + defField "has-chapters" (stHasChapters st) $ + (case T.uncons . render Nothing <$> + getField "papersize" metadata of + -- uppercase a4, a5, etc. + Just (Just ('A', ds)) + | not (T.null ds) && T.all isDigit ds + -> resetField "papersize" ("a" <> ds) + _ -> id) + metadata + return $ render colwidth $ + case writerTemplate options of + Nothing -> main + Just tpl -> renderTemplate tpl context + +data StringContext = TextString + | URLString + | CodeString + deriving (Eq) + +-- escape things as needed for SILE +stringToSILE :: PandocMonad m => StringContext -> Text -> LW m Text +stringToSILE context zs = do + opts <- gets stOptions + return $ T.pack $ + foldr (go opts context) mempty $ T.unpack $ zs + where + go :: WriterOptions -> StringContext -> Char -> String -> String + go _ ctx x xs = + let isUrl = ctx == URLString + emits s = s <> xs + emitc c = c : xs + in case x of + '{' -> emits "\\{" + '}' -> emits "\\}" + '%' -> emits "\\%" + '\\'| isUrl -> emitc '/' -- NB. / works as path sep even on Windows + | otherwise -> emits "\\\\" + _ -> emitc x + +toLabel :: PandocMonad m => Text -> LW m Text +toLabel z = go `fmap` stringToSILE URLString z + where + go = T.concatMap $ \x -> case x of + _ | (isLetter x || isDigit x) && isAscii x -> T.singleton x + | x `elemText` "_-+=:;." -> T.singleton x + | otherwise -> T.pack $ "ux" <> printf "%x" (ord x) + +toOptions :: PandocMonad m => Text -> [Text] -> [(Text, Text)] -> LW m [Text] +toOptions ident classes kvs = do + ref <- toLabel ident + -- lang <- toLang $ lookup "lang" kvs + let classes' = [ val | (val) <- classes ] + let classes'' = T.intercalate "," classes' + let options = (if T.null ident + then [] + else [ "id=" <> ref ]) <> + (if null classes' + then [] + else [ "classes=\"" <> classes'' <> "\"" ] ) <> + (if null kvs + then [] + else [ key <> "=" <> attr | (key, attr) <- kvs ]) + return options + +inCmd :: Text -> Doc Text -> Doc Text +inCmd cmd content = do + char '\\' <> literal cmd <> braces content + +inOptCmd :: Text -> [Text] -> Doc Text -> Doc Text +inOptCmd cmd args content = do + let args' = if null args + then empty + else brackets $ hcat (intersperse "," (map literal args)) + char '\\' <> literal cmd <> args' <> (if isEmpty content then empty else braces content) + +inOptEnv :: Text -> [Text] -> Doc Text -> Doc Text +inOptEnv cmd args content = do + let args' = if null args + then empty + else brackets $ hcat (intersperse "," (map literal args)) + cmd' = braces (literal cmd) + literal "\\begin" <> args' <> cmd' + $$ content + $$ literal "\\end" <> cmd' + +-- | Convert Pandoc block element to SILE. +blockToSILE :: PandocMonad m + => Block -- ^ Block to convert + -> LW m (Doc Text) +blockToSILE Null = return empty +blockToSILE (Div (ident,classes,kvs) bs) = do + options <- toOptions ident classes kvs + content <- blockListToSILE bs + return $ inOptEnv "Div" options content +blockToSILE (Plain lst) = + inlineListToSILE lst +blockToSILE (Para [Str ".",Space,Str ".",Space,Str "."]) = do + inlineListToSILE [Str ".",Space,Str ".",Space,Str "."] +blockToSILE (Para lst) = + inlineListToSILE lst +blockToSILE (LineBlock lns) = + blockToSILE $ linesToPara lns +blockToSILE (BlockQuote lst) = do + content <- blockListToSILE lst + return $ inOptEnv "BlockQuote" [] content +blockToSILE (CodeBlock (ident,classes,kvs) str) = do + options <- toOptions ident classes kvs + content <- liftM literal $ stringToSILE CodeString str + return $ inOptEnv "CodeBlock" options content +blockToSILE b@(RawBlock f x) + | f == Format "sile" || f == Format "sil" + = return $ literal x + | otherwise = do + report $ BlockNotRendered b + return empty +blockToSILE (BulletList lst) = do + items <- mapM listItemToSILE lst + let content = vcat items + return $ inOptEnv "BulletList" [] content +blockToSILE (OrderedList _ []) = return empty -- otherwise error +blockToSILE (OrderedList (start, numstyle, _) lst) = do + st <- get + let oldlevel = stOLLevel st + put $ st {stOLLevel = oldlevel + 1} + items <- mapM listItemToSILE lst + let content = vcat items + modify (\s -> s {stOLLevel = oldlevel}) + let numstyle' = case numstyle of + Decimal -> "arabic" + UpperRoman -> "Roman" + LowerRoman -> "roman" + UpperAlpha -> "Alpha" + LowerAlpha -> "alpha" + Example -> "arabic" + DefaultStyle -> "arabic" + let start' = T.pack $ show start + let opts = [("numberstyle", numstyle')] ++ + [("start", start') | start > 1] ++ + [("tight", "true") | isTightList lst] + options <- toOptions "" [] opts + return $ inOptEnv "OrderedList" options content +blockToSILE (DefinitionList []) = return empty +blockToSILE (DefinitionList lst) = do + items <- mapM defListItemToSILE lst + let content = vcat items + let opts = [("tight", "true") | all isTightList (map snd lst)] + options <- toOptions "" [] opts + return $ inOptEnv "DefinitionList" options content +blockToSILE HorizontalRule = + return "\\HorizontalRule" +blockToSILE (Header level (id',classes,_) lst) = do + hdr <- sectionHeader classes id' level lst + return hdr +blockToSILE Table{} = + return "\\script{SU.warn(\"Unimplemented, tables!\")}" + +blockListToSILE :: PandocMonad m => [Block] -> LW m (Doc Text) +blockListToSILE lst = + vsep `fmap` mapM (\b -> setEmptyLine True >> blockToSILE b) lst + +listItemToSILE :: PandocMonad m => [Block] -> LW m (Doc Text) +listItemToSILE lst = + inCmd "ListItem" <$> blockListToSILE lst + +defListItemToSILE :: PandocMonad m => ([Inline], [[Block]]) -> LW m (Doc Text) +defListItemToSILE (term, defs) = do + term' <- inlineListToSILE term + def' <- liftM vsep $ mapM blockListToSILE defs + return $ inCmd "term" term' $$ + inCmd "definition" def' + +sectionHeader :: PandocMonad m + => [Text] -- classes + -> Text + -> Int + -> [Inline] + -> LW m (Doc Text) +sectionHeader classes id' level lst = do + content <- inlineListToSILE lst + book <- gets stHasChapters + opts <- gets stOptions + let topLevelDivision = if book && writerTopLevelDivision opts == TopLevelDefault + then TopLevelChapter + else writerTopLevelDivision opts + let level' = case topLevelDivision of + TopLevelPart -> level - 2 + TopLevelChapter -> level - 1 + TopLevelSection -> level + TopLevelDefault -> level + let level'' = T.pack $ show level' + let sectionType = case level' of + -1 -> "part" + 0 -> "chapter" + 1 -> "section" + 2 -> "subsection" + _ -> "" + options <- toOptions id' classes [ ("level", level''), ("type", sectionType) ] + return $ inOptCmd "Header" options content + +-- | Convert list of inline elements to SILE. +inlineListToSILE :: PandocMonad m + => [Inline] -- ^ Inlines to convert + -> LW m (Doc Text) +inlineListToSILE lst = hcat <$> + mapM inlineToSILE (fixLineInitialSpaces $ lst) + where fixLineInitialSpaces [] = [] + fixLineInitialSpaces (LineBreak : Str s : xs) + | Just ('\160', _) <- T.uncons s + = LineBreak : fixNbsps s <> fixLineInitialSpaces xs + fixLineInitialSpaces (x:xs) = x : fixLineInitialSpaces xs + fixNbsps s = let (ys,zs) = T.span (=='\160') s + in replicate (T.length ys) hspace <> [Str zs] + hspace = RawInline "sile" "\\nbsp{}" -- TODO: use U+00A0 + +-- | Convert inline element to SILE +inlineToSILE :: PandocMonad m + => Inline -- ^ Inline to convert + -> LW m (Doc Text) +inlineToSILE (Span (id',classes,kvs) ils) = do + content <- inlineListToSILE ils + let classToCommand = [ "csl-no-emph", "csl-no-strong", "csl-no-smallcaps" ] + let cmds = filter (`elem` classToCommand) classes + let classes' = filter (`notElem` classToCommand) classes + options <- toOptions id' classes' kvs + return $ if null cmds + then inOptCmd "Span" options content + else inOptCmd "Span" options $ foldr inCmd content cmds + +inlineToSILE (Emph lst) = + inCmd "Emph" <$> inlineListToSILE lst +inlineToSILE (Strong lst) = + inCmd "Strong" <$> inlineListToSILE lst +inlineToSILE (Strikeout lst) = + inCmd "Strikeout" <$> inlineListToSILE lst +inlineToSILE (Superscript lst) = + inCmd "Superscript" <$> inlineListToSILE lst +inlineToSILE (Subscript lst) = + inCmd "textsubscript" <$> inlineListToSILE lst +inlineToSILE (SmallCaps lst) = + inCmd "SmallCaps" <$> inlineListToSILE lst +inlineToSILE (Cite cits lst) = do + st <- get + let opts = stOptions st + case writerCiteMethod opts of + Natbib -> citationsToNatbib cits + _ -> inlineListToSILE lst + +inlineToSILE (Code (_,_,_) str) = do + content <- liftM literal $ stringToSILE TextString str + return $ inCmd "code" content +inlineToSILE (Quoted SingleQuote lst) = do + opts <- gets stOptions + content <- inlineListToSILE lst + return $ if isEnabled Ext_smart opts + then "‘" <> content <> "’" + else "'" <> content <> "'" +inlineToSILE (Quoted DoubleQuote lst) = do + opts <- gets stOptions + content <- inlineListToSILE lst + return $ if isEnabled Ext_smart opts + then "“" <> content <> "”" + else "\"" <> content <> "\"" +inlineToSILE (Str str) = do + setEmptyLine False + liftM literal $ stringToSILE TextString str +inlineToSILE (Math _ str) = do + content <- liftM literal $ stringToSILE TextString str + return $ inCmd "Math" content +inlineToSILE (RawInline _ str) = do + setEmptyLine False + return $ literal str +inlineToSILE LineBreak = return $ "\\hfill\\break" <> cr +inlineToSILE SoftBreak = do + wrapText <- gets (writerWrapText . stOptions) + case wrapText of + WrapAuto -> return space + WrapNone -> return space + WrapPreserve -> return cr +inlineToSILE Space = return space +inlineToSILE (Link (ident,classes,kvs) txt (src,_)) + | Just ('#', ident') <- T.uncons src = do + content <- inlineListToSILE txt + options <- toOptions ident' classes kvs + return $ inOptCmd "pdf:link" options content + | otherwise = do + content <- inlineListToSILE txt + src' <- stringToSILE URLString (escapeURI src) + options <- toOptions ident classes (kvs ++ [("src", src')]) + return $ inOptCmd "href" options content +inlineToSILE il@(Image _ _ (src, _)) + | Just _ <- T.stripPrefix "data:" src = do + report $ InlineNotRendered il + return empty +inlineToSILE (Image (ident,classes,kvs) txt (source, tit)) = do + setEmptyLine False + content <- inlineListToSILE txt + let source' = if isURI source + then source + else T.pack $ unEscapeString $ T.unpack source + source'' <- stringToSILE URLString source' + let opts = kvs ++ + [("src", source'')] ++ + [("title", tit) | not (T.null tit)] + options <- toOptions ident classes opts + return $ inOptCmd "img" options content +inlineToSILE (Note content) = do + setEmptyLine False + contents' <- blockListToSILE content + let optnl = case reverse content of + (CodeBlock _ _ : _) -> cr + _ -> empty + let noteContents = nest 2 contents' <> optnl + return $ "\\footnote" <> braces noteContents + +setEmptyLine :: PandocMonad m => Bool -> LW m () +setEmptyLine b = modify $ \st -> st{ stEmptyLine = b } + +citationsToNatbib :: PandocMonad m => [Citation] -> LW m (Doc Text) +citationsToNatbib + [one] + = citeCommand c p s k + where + Citation { citationId = k + , citationPrefix = p + , citationSuffix = s + , citationMode = m + } + = one + c = case m of + AuthorInText -> "citet" + SuppressAuthor -> "citeyearpar" + NormalCitation -> "citep" + +citationsToNatbib cits + | noPrefix (tail cits) && noSuffix (init cits) && ismode NormalCitation cits + = citeCommand "citep" p s ks + where + noPrefix = all (null . citationPrefix) + noSuffix = all (null . citationSuffix) + ismode m = all ((==) m . citationMode) + p = citationPrefix $ + head cits + s = citationSuffix $ + last cits + ks = T.intercalate ", " $ map citationId cits + +citationsToNatbib (c:cs) | citationMode c == AuthorInText = do + author <- citeCommand "citeauthor" [] [] (citationId c) + cits <- citationsToNatbib (c { citationMode = SuppressAuthor } : cs) + return $ author <+> cits + +citationsToNatbib cits = do + cits' <- mapM convertOne cits + return $ text "\\citetext{" <> foldl' combineTwo empty cits' <> text "}" + where + combineTwo a b | isEmpty a = b + | otherwise = a <> text "; " <> b + convertOne Citation { citationId = k + , citationPrefix = p + , citationSuffix = s + , citationMode = m + } + = case m of + AuthorInText -> citeCommand "citealt" p s k + SuppressAuthor -> citeCommand "citeyear" p s k + NormalCitation -> citeCommand "citealp" p s k + +citeCommand :: PandocMonad m + => Text -> [Inline] -> [Inline] -> Text -> LW m (Doc Text) +citeCommand c p s k = do + args <- citeArguments p s k + return $ literal ("\\" <> c) <> args + +citeArguments :: PandocMonad m + => [Inline] -> [Inline] -> Text -> LW m (Doc Text) +citeArguments p s k = do + let s' = stripLocatorBraces $ case s of + (Str t : r) -> case T.uncons t of + Just (x, xs) + | T.null xs + , isPunctuation x -> dropWhile (== Space) r + | isPunctuation x -> Str xs : r + _ -> s + _ -> s + pdoc <- inlineListToSILE p + sdoc <- inlineListToSILE s' + let optargs = case (isEmpty pdoc, isEmpty sdoc) of + (True, True ) -> empty + (True, False) -> brackets sdoc + (_ , _ ) -> brackets pdoc <> brackets sdoc + return $ optargs <> braces (literal k) + +-- strip off {} used to define locator in pandoc-citeproc; see #5722 +stripLocatorBraces :: [Inline] -> [Inline] +stripLocatorBraces = walk go + where go (Str xs) = Str $ T.filter (\c -> c /= '{' && c /= '}') xs + go x = x + diff --git a/test/Tests/Writers/SILE.hs b/test/Tests/Writers/SILE.hs new file mode 100644 index 000000000000..f68eb05af9a8 --- /dev/null +++ b/test/Tests/Writers/SILE.hs @@ -0,0 +1,78 @@ +{-# LANGUAGE NoImplicitPrelude #-} +{-# LANGUAGE OverloadedStrings #-} +module Tests.Writers.SILE (tests) where + +import Prelude +import Data.Text (unpack) +import Test.Tasty +import Tests.Helpers +import Text.Pandoc +import Text.Pandoc.Arbitrary () +import Text.Pandoc.Builder + +sile :: (ToPandoc a) => a -> String +sile = sileWithOpts def + +sileWithOpts :: (ToPandoc a) => WriterOptions -> a -> String +sileWithOpts opts = unpack . purely (writeSILE opts) . toPandoc + +{- + "my test" =: X =?> Y + +is shorthand for + + test sile "my test" $ X =?> Y + +which is in turn shorthand for + + test sile "my test" (X,Y) +-} + +infix 4 =: +(=:) :: (ToString a, ToPandoc a) + => String -> (a, String) -> TestTree +(=:) = test sile + +tests :: [TestTree] +tests = [testGroup "BlockQuote" + [ "simple" =: blockQuote (para "foo") =?> + "\\begin{BlockQuote}\nfoo\n\\end{BlockQuote}" + ] + ,testGroup "BulletList" + [ "simple" =: bulletList [para "foo", para "bar"] =?> + "\\begin{BulletList}\n\\ListItem{foo}\n\\ListItem{bar}\n\\end{BulletList}" + ] + ,testGroup "CodeBlock" + [ "simple" =: codeBlock "foo" =?> + "\\begin{CodeBlock}\nfoo\n\\end{CodeBlock}" + , "with id" =: codeBlockWith ("bar", ["stuff"], []) "foo" =?> + "\\begin[id=bar,classes=\"stuff\"]{CodeBlock}\nfoo\n\\end{CodeBlock}" + ] + , testGroup "definition lists" + [ "with internal link" =: definitionList [(link "#go" "" (str "testing"), + [plain (text "hi there")])] =?> + "\\begin[tight=true]{DefinitionList}\n\\term{\\pdf:link[id=go]{testing}}\n\\definition{hi there}\n\\end{DefinitionList}" + ] + , testGroup "Header" + [ "chapter" =: header 0 (text "foo") =?> + "\\Header[level=0,type=chapter]{foo}" + , "section" =: header 1 (text "foo") =?> + "\\Header[level=1,type=section]{foo}" + , "subsection" =: header 2 (text "foo") =?> + "\\Header[level=2,type=subsection]{foo}" + -- , "part" =: header 0 (text "foo") =?> + -- "\\Header[level=-1,type=part]{foo}" + , "unnumbered with id note" =: + headerWith ("foo",["unnumbered"],[]) 1 + (text "foo" <> note (plain $ text "bar")) =?> + "\\Header[id=foo,classes=\"unnumbered\",level=1,type=section]{foo\\footnote{bar}}" + , "in list item" =: bulletList [header 2 (text "foo")] =?> + "\\begin{BulletList}\n\\ListItem{\\Header[level=2,type=subsection]{foo}}\n\\end{BulletList}" + , "in definition list item" =: + definitionList [(text "foo", [header 2 (text "bar"), + para $ text "baz"])] =?> + "\\begin{DefinitionList}\n\\term{foo}\n\\definition{\\Header[level=2,type=subsection]{bar}\n\nbaz}\n\\end{DefinitionList}" + , "containing image" =: header 1 (image "imgs/foo.jpg" "" (text "Alt text")) =?> + "\\Header[level=1,type=section]{\\img[src=imgs/foo.jpg]{Alt text}}" + ] + ] diff --git a/test/test-pandoc.hs b/test/test-pandoc.hs index bb4db90b9409..224492756da2 100644 --- a/test/test-pandoc.hs +++ b/test/test-pandoc.hs @@ -45,6 +45,7 @@ import qualified Tests.Writers.Plain import qualified Tests.Writers.Powerpoint import qualified Tests.Writers.RST import qualified Tests.Writers.AnnotatedTable +import qualified Tests.Writers.SILE import qualified Tests.Writers.TEI import Tests.Helpers (findPandoc) import Text.Pandoc.Shared (inDirectory) @@ -68,6 +69,7 @@ tests pandocPath = testGroup "pandoc tests" , testGroup "AsciiDoc" Tests.Writers.AsciiDoc.tests , testGroup "Docx" Tests.Writers.Docx.tests , testGroup "RST" Tests.Writers.RST.tests + , testGroup "SILE" Tests.Writers.SILE.tests , testGroup "TEI" Tests.Writers.TEI.tests , testGroup "Muse" Tests.Writers.Muse.tests , testGroup "FB2" Tests.Writers.FB2.tests diff --git a/test/writer.sile b/test/writer.sile new file mode 100644 index 000000000000..3fcb9e94aaea --- /dev/null +++ b/test/writer.sile @@ -0,0 +1,758 @@ +This is a set of tests for pandoc. Most of them are adapted from John +Gruber’s markdown test suite. + +\HorizontalRule + +\Header[id=headers,level=1,type=section]{Headers} + +\Header[id=level-2-with-an-embedded-link,level=2,type=subsection]{Level +2 with an \href[src=/url]{embedded link}} + +\Header[id=level-3-with-emphasis,level=3,type=]{Level 3 with +\Emph{emphasis}} + +\Header[id=level-4,level=4,type=]{Level 4} + +\Header[id=level-5,level=5,type=]{Level 5} + +\Header[id=level-1,level=1,type=section]{Level 1} + +\Header[id=level-2-with-emphasis,level=2,type=subsection]{Level 2 with +\Emph{emphasis}} + +\Header[id=level-3,level=3,type=]{Level 3} + +with no blank line + +\Header[id=level-2,level=2,type=subsection]{Level 2} + +with no blank line + +\HorizontalRule + +\Header[id=paragraphs,level=1,type=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\hfill\break +here. + +\HorizontalRule + +\Header[id=block-quotes,level=1,type=section]{Block Quotes} + +E-mail style: + +\begin{BlockQuote} +This is a block quote. It is pretty short. +\end{BlockQuote} + +\begin{BlockQuote} +Code in a block quote: + +\begin{CodeBlock} +sub status \{ + print "working"; +\} +\end{CodeBlock} + +A list: + +\begin[numberstyle=arabic,tight=true]{OrderedList} +\ListItem{item one} +\ListItem{item two} +\end{OrderedList} + +Nested block quotes: + +\begin{BlockQuote} +nested +\end{BlockQuote} + +\begin{BlockQuote} +nested +\end{BlockQuote} +\end{BlockQuote} + +This should not be a block quote: 2 > 1. + +And a following paragraph. + +\HorizontalRule + +\Header[id=code-blocks,level=1,type=section]{Code Blocks} + +Code: + +\begin{CodeBlock} +---- (should be four hyphens) + +sub status \{ + print "working"; +\} + +this code block is indented by one tab +\end{CodeBlock} + +And: + +\begin{CodeBlock} + this code block is indented by two tabs + +These should not be escaped: \\$ \\\\ \\> \\[ \\\{ +\end{CodeBlock} + +\HorizontalRule + +\Header[id=lists,level=1,type=section]{Lists} + +\Header[id=unordered,level=2,type=subsection]{Unordered} + +Asterisks tight: + +\begin{BulletList} +\ListItem{asterisk 1} +\ListItem{asterisk 2} +\ListItem{asterisk 3} +\end{BulletList} + +Asterisks loose: + +\begin{BulletList} +\ListItem{asterisk 1} +\ListItem{asterisk 2} +\ListItem{asterisk 3} +\end{BulletList} + +Pluses tight: + +\begin{BulletList} +\ListItem{Plus 1} +\ListItem{Plus 2} +\ListItem{Plus 3} +\end{BulletList} + +Pluses loose: + +\begin{BulletList} +\ListItem{Plus 1} +\ListItem{Plus 2} +\ListItem{Plus 3} +\end{BulletList} + +Minuses tight: + +\begin{BulletList} +\ListItem{Minus 1} +\ListItem{Minus 2} +\ListItem{Minus 3} +\end{BulletList} + +Minuses loose: + +\begin{BulletList} +\ListItem{Minus 1} +\ListItem{Minus 2} +\ListItem{Minus 3} +\end{BulletList} + +\Header[id=ordered,level=2,type=subsection]{Ordered} + +Tight: + +\begin[numberstyle=arabic,tight=true]{OrderedList} +\ListItem{First} +\ListItem{Second} +\ListItem{Third} +\end{OrderedList} + +and: + +\begin[numberstyle=arabic,tight=true]{OrderedList} +\ListItem{One} +\ListItem{Two} +\ListItem{Three} +\end{OrderedList} + +Loose using tabs: + +\begin[numberstyle=arabic]{OrderedList} +\ListItem{First} +\ListItem{Second} +\ListItem{Third} +\end{OrderedList} + +and using spaces: + +\begin[numberstyle=arabic]{OrderedList} +\ListItem{One} +\ListItem{Two} +\ListItem{Three} +\end{OrderedList} + +Multiple paragraphs: + +\begin[numberstyle=arabic]{OrderedList} +\ListItem{Item 1, graf one. + +Item 1. graf two. The quick brown fox jumped over the lazy dog’s back.} +\ListItem{Item 2.} +\ListItem{Item 3.} +\end{OrderedList} + +\Header[id=nested,level=2,type=subsection]{Nested} + +\begin{BulletList} +\ListItem{Tab + +\begin{BulletList} +\ListItem{Tab + +\begin{BulletList} +\ListItem{Tab} +\end{BulletList}} +\end{BulletList}} +\end{BulletList} + +Here’s another: + +\begin[numberstyle=arabic,tight=true]{OrderedList} +\ListItem{First} +\ListItem{Second: + +\begin{BulletList} +\ListItem{Fee} +\ListItem{Fie} +\ListItem{Foe} +\end{BulletList}} +\ListItem{Third} +\end{OrderedList} + +Same thing but with paragraphs: + +\begin[numberstyle=arabic]{OrderedList} +\ListItem{First} +\ListItem{Second: + +\begin{BulletList} +\ListItem{Fee} +\ListItem{Fie} +\ListItem{Foe} +\end{BulletList}} +\ListItem{Third} +\end{OrderedList} + +\Header[id=tabs-and-spaces,level=2,type=subsection]{Tabs and spaces} + +\begin{BulletList} +\ListItem{this is a list item indented with tabs} +\ListItem{this is a list item indented with spaces + +\begin{BulletList} +\ListItem{this is an example list item indented with tabs} +\ListItem{this is an example list item indented with spaces} +\end{BulletList}} +\end{BulletList} + +\Header[id=fancy-list-markers,level=2,type=subsection]{Fancy list +markers} + +\begin[numberstyle=arabic,start=2]{OrderedList} +\ListItem{begins with 2} +\ListItem{and now 3 + +with a continuation + +\begin[numberstyle=roman,start=4,tight=true]{OrderedList} +\ListItem{sublist with roman numerals, starting with 4} +\ListItem{more items + +\begin[numberstyle=Alpha,tight=true]{OrderedList} +\ListItem{a subsublist} +\ListItem{a subsublist} +\end{OrderedList}} +\end{OrderedList}} +\end{OrderedList} + +Nesting: + +\begin[numberstyle=Alpha,tight=true]{OrderedList} +\ListItem{Upper Alpha + +\begin[numberstyle=Roman,tight=true]{OrderedList} +\ListItem{Upper Roman. + +\begin[numberstyle=arabic,start=6,tight=true]{OrderedList} +\ListItem{Decimal start with 6 + +\begin[numberstyle=alpha,start=3,tight=true]{OrderedList} +\ListItem{Lower alpha with paren} +\end{OrderedList}} +\end{OrderedList}} +\end{OrderedList}} +\end{OrderedList} + +Autonumbering: + +\begin[numberstyle=arabic,tight=true]{OrderedList} +\ListItem{Autonumber.} +\ListItem{More. + +\begin[numberstyle=arabic,tight=true]{OrderedList} +\ListItem{Nested.} +\end{OrderedList}} +\end{OrderedList} + +Should not be a list item: + +M.A. 2007 + +B. Williams + +\HorizontalRule + +\Header[id=definition-lists,level=1,type=section]{Definition Lists} + +Tight using spaces: + +\begin[tight=true]{DefinitionList} +\term{apple} +\definition{red fruit} +\term{orange} +\definition{orange fruit} +\term{banana} +\definition{yellow fruit} +\end{DefinitionList} + +Tight using tabs: + +\begin[tight=true]{DefinitionList} +\term{apple} +\definition{red fruit} +\term{orange} +\definition{orange fruit} +\term{banana} +\definition{yellow fruit} +\end{DefinitionList} + +Loose: + +\begin{DefinitionList} +\term{apple} +\definition{red fruit} +\term{orange} +\definition{orange fruit} +\term{banana} +\definition{yellow fruit} +\end{DefinitionList} + +Multiple blocks with italics: + +\begin{DefinitionList} +\term{\Emph{apple}} +\definition{red fruit + +contains seeds, crisp, pleasant to taste} +\term{\Emph{orange}} +\definition{orange fruit + +\begin{CodeBlock} +\{ orange code block \} +\end{CodeBlock} + +\begin{BlockQuote} +orange block quote +\end{BlockQuote}} +\end{DefinitionList} + +Multiple definitions, tight: + +\begin[tight=true]{DefinitionList} +\term{apple} +\definition{red fruit + +computer} +\term{orange} +\definition{orange fruit + +bank} +\end{DefinitionList} + +Multiple definitions, loose: + +\begin{DefinitionList} +\term{apple} +\definition{red fruit + +computer} +\term{orange} +\definition{orange fruit + +bank} +\end{DefinitionList} + +Blank line after term, indented marker, alternate markers: + +\begin{DefinitionList} +\term{apple} +\definition{red fruit + +computer} +\term{orange} +\definition{orange fruit + +\begin[numberstyle=arabic,tight=true]{OrderedList} +\ListItem{sublist} +\ListItem{sublist} +\end{OrderedList}} +\end{DefinitionList} + +\Header[id=html-blocks,level=1,type=section]{HTML Blocks} + +Simple block on one line: + +\begin{Div} +foo +\end{Div} + +And nested without indentation: + +\begin{Div} +\begin{Div} +\begin{Div} +foo +\end{Div} +\end{Div} + +\begin{Div} +bar +\end{Div} +\end{Div} + +Interpreted markdown in a table: + +This is \Emph{emphasized} + +And this is \Strong{strong} + +Here’s a simple block: + +\begin{Div} +foo +\end{Div} + +This should be a code block, though: + +\begin{CodeBlock} +
+ foo +
+\end{CodeBlock} + +As should this: + +\begin{CodeBlock} +
foo
+\end{CodeBlock} + +Now, nested: + +\begin{Div} +\begin{Div} +\begin{Div} +foo +\end{Div} +\end{Div} +\end{Div} + +This should just be an HTML comment: + +Multiline: + +Code block: + +\begin{CodeBlock} + +\end{CodeBlock} + +Just plain comment, with trailing spaces on the line: + +Code: + +\begin{CodeBlock} +
+\end{CodeBlock} + +Hr’s: + +\HorizontalRule + +\Header[id=inline-markup,level=1,type=section]{Inline Markup} + +This is \Emph{emphasized}, and so \Emph{is this}. + +This is \Strong{strong}, and so \Strong{is this}. + +An \Emph{\href[src=/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: \code{>}, \code{$}, \code{\\}, \code{\\$}, \code{}. + +\Strikeout{This is \Emph{strikeout}.} + +Superscripts: a\Superscript{bc}d a\Superscript{\Emph{hello}} +a\Superscript{hello there}. + +Subscripts: H\textsubscript{2}O, H\textsubscript{23}O, +H\textsubscript{many of them}O. + +These should not be superscripts or subscripts, because of the unescaped +spaces: a^b c^d, a~b c~d. + +\HorizontalRule + +\Header[id=smart-quotes-ellipses-dashes,level=1,type=section]{Smart +quotes, ellipses, dashes} + +“Hello,” said the spider. “‘Shelob’ is my name.” + +‘A’, ‘B’, and ‘C’ are letters. + +‘Oak,’ ‘elm,’ and ‘beech’ are names of trees. So is ‘pine.’ + +‘He said, “I want to go.”’ Were you alive in the 70’s? + +Here is some quoted ‘\code{code}’ and a +“\href[src=http://example.com/?foo=1&bar=2]{quoted link}”. + +Some dashes: one—two — three—four — five. + +Dashes between numbers: 5–7, 255–66, 1987–1999. + +Ellipses…and…and…. + +\HorizontalRule + +\Header[id=latex,level=1,type=section]{LaTeX} + +\begin{BulletList} +\ListItem{\cite[22-23]{smith.1899}} +\ListItem{\Math{2+2=4}} +\ListItem{\Math{x \\in y}} +\ListItem{\Math{\\alpha \\wedge \\omega}} +\ListItem{\Math{223}} +\ListItem{\Math{p}-Tree} +\ListItem{Here’s some display math: +\Math{\\frac\{d\}\{dx\}f(x)=\\lim_\{h\\to 0\}\\frac\{f(x+h)-f(x)\}\{h\}}} +\ListItem{Here’s one that has a line break in it: +\Math{\\alpha + \\omega \\times x^2}.} +\end{BulletList} + +These shouldn’t be math: + +\begin{BulletList} +\ListItem{To get the famous equation, write \code{$e = mc^2$}.} +\ListItem{$22,000 is a \Emph{lot} of money. So is $34,000. (It worked if +“lot” is emphasized.)} +\ListItem{Shoes ($20) and socks ($5).} +\ListItem{Escaped \code{$}: $73 \Emph{this should be emphasized} 23$.} +\end{BulletList} + +Here’s a LaTeX table: + +\HorizontalRule + +\Header[id=special-characters,level=1,type=section]{Special Characters} + +Here is some unicode: + +\begin{BulletList} +\ListItem{I hat: Î} +\ListItem{o umlaut: ö} +\ListItem{section: §} +\ListItem{set membership: ∈} +\ListItem{copyright: ©} +\end{BulletList} + +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: - + +\HorizontalRule + +\Header[id=links,level=1,type=section]{Links} + +\Header[id=explicit,level=2,type=subsection]{Explicit} + +Just a \href[src=/url/]{URL}. + +\href[src=/url/]{URL and title}. + +\href[src=/url/]{URL and title}. + +\href[src=/url/]{URL and title}. + +\href[src=/url/]{URL and title} + +\href[src=/url/]{URL and title} + +\href[src=/url/with_underscore]{with_underscore} + +\href[src=mailto:nobody@nowhere.net]{Email link} + +\href[src=]{Empty}. + +\Header[id=reference,level=2,type=subsection]{Reference} + +Foo \href[src=/url/]{bar}. + +With \href[src=/url/]{embedded [brackets]}. + +\href[src=/url/]{b} by itself should be a link. + +Indented \href[src=/url]{once}. + +Indented \href[src=/url]{twice}. + +Indented \href[src=/url]{thrice}. + +This should [not][] be a link. + +\begin{CodeBlock} +[not]: /url +\end{CodeBlock} + +Foo \href[src=/url/]{bar}. + +Foo \href[src=/url/]{biz}. + +\Header[id=with-ampersands,level=2,type=subsection]{With ampersands} + +Here’s a \href[src=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: +\href[src=http://att.com/]{AT&T}. + +Here’s an \href[src=/script?foo=1&bar=2]{inline link}. + +Here’s an \href[src=/script?foo=1&bar=2]{inline link in pointy braces}. + +\Header[id=autolinks,level=2,type=subsection]{Autolinks} + +With an ampersand: +\href[classes="uri",src=http://example.com/?foo=1&bar=2]{http://example.com/?foo=1&bar=2} + +\begin{BulletList} +\ListItem{In a list?} +\ListItem{\href[classes="uri",src=http://example.com/]{http://example.com/}} +\ListItem{It should.} +\end{BulletList} + +An e-mail address: +\href[classes="email",src=mailto:nobody@nowhere.net]{nobody@nowhere.net} + +\begin{BlockQuote} +Blockquoted: +\href[classes="uri",src=http://example.com/]{http://example.com/} +\end{BlockQuote} + +Auto-links should not occur here: \code{} + +\begin{CodeBlock} +or here: +\end{CodeBlock} + +\HorizontalRule + +\Header[id=images,level=1,type=section]{Images} + +From “Voyage dans la Lune” by Georges Melies (1902): + +\img[src=lalune.jpg,title=fig:Voyage dans la Lune]{lalune} + +Here is a movie \img[src=movie.jpg]{movie} icon. + +\HorizontalRule + +\Header[id=footnotes,level=1,type=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). + + \begin{CodeBlock} + \{ \} + \end{CodeBlock} + + 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 \Emph{not} be a +footnote reference, because it contains a space.[^my note] Here is an +inline note.\footnote{This is \Emph{easier} to type. Inline notes may + contain \href[src=http://google.com]{links} and \code{]} verbatim + characters, as well as [bracketed text].} + +\begin{BlockQuote} +Notes can go in quotes.\footnote{In quote.} +\end{BlockQuote} + +\begin[numberstyle=arabic,tight=true]{OrderedList} +\ListItem{And in list items.\footnote{In list.}} +\end{OrderedList} + +This paragraph should not be part of the note, as it is not indented.