Add text wrapping to HTML output.
Previously the HTML writer was exceptional in not being sensitive to the `--wrap` option. With this change `--wrap` now works for HTML. The default (as with other formats) is automatic wrapping to 72 columns. A new internal module, T.P.Writers.Blaze, exports `layoutMarkup`. This converts a blaze Html structure into a doclayout Doc Text. In addition, we now add a line break between an `img` tag and the associated `figcaption`. Note: Output is never wrapped in `writeHtmlStringForEPUB`. This accords with previous behavior since previously the HTML writer was insensitive to `--wrap` settings. There's no real need to wrap HTML inside a zipped container. Note that the contents of script, textarea, and pre tags are always laid out with the `flush` combinator, so that unwanted spaces won't be introduced if these occur in an indented context in a template. Closes #7764.
This commit is contained in:
parent
0bdf373157
commit
7a9832166e
41 changed files with 475 additions and 172 deletions
|
@ -790,7 +790,6 @@ header when requesting a document from a URL:
|
|||
preserve the wrapping from the source document (that is,
|
||||
where there are nonsemantic newlines in the source, there
|
||||
will be nonsemantic newlines in the output as well).
|
||||
Automatic wrapping does not currently work in HTML output.
|
||||
In `ipynb` output, this option affects wrapping of the
|
||||
contents of markdown cells.
|
||||
|
||||
|
|
|
@ -688,6 +688,7 @@ library
|
|||
Text.Pandoc.Writers.Markdown.Types,
|
||||
Text.Pandoc.Writers.Markdown.Inline,
|
||||
Text.Pandoc.Writers.Roff,
|
||||
Text.Pandoc.Writers.Blaze,
|
||||
Text.Pandoc.Writers.Powerpoint.Presentation,
|
||||
Text.Pandoc.Writers.Powerpoint.Output,
|
||||
Text.Pandoc.Lua.ErrorConversion,
|
||||
|
|
139
src/Text/Pandoc/Writers/Blaze.hs
Normal file
139
src/Text/Pandoc/Writers/Blaze.hs
Normal file
|
@ -0,0 +1,139 @@
|
|||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{- |
|
||||
Module : Text.Pandoc.Writers.Shared
|
||||
Copyright : Copyright (C) 2021 John MacFarlane
|
||||
License : GNU GPL, version 2 or above
|
||||
|
||||
Maintainer : John MacFarlane <jgm@berkeley.edu>
|
||||
Stability : alpha
|
||||
Portability : portable
|
||||
|
||||
Render blaze-html Html to DocLayout document (so it can be wrapped).
|
||||
-}
|
||||
module Text.Pandoc.Writers.Blaze ( layoutMarkup )
|
||||
where
|
||||
import Text.Blaze
|
||||
import qualified Data.ByteString as S
|
||||
import Data.List (isInfixOf)
|
||||
import Data.Text.Encoding (decodeUtf8)
|
||||
import qualified Data.Text as T
|
||||
import Data.Text (Text)
|
||||
import Text.DocLayout hiding (Text, Empty)
|
||||
import Text.Blaze.Internal (ChoiceString(..), getText, MarkupM(..))
|
||||
|
||||
layoutMarkup :: Markup -> Doc T.Text
|
||||
layoutMarkup = go True mempty
|
||||
where
|
||||
go :: Bool -> Doc T.Text -> MarkupM b -> Doc T.Text
|
||||
go wrap attrs (Parent _ open close content) =
|
||||
let open' = getText open
|
||||
in literal open'
|
||||
<> attrs
|
||||
<> char '>'
|
||||
<> (if allowsWrap open'
|
||||
then go wrap mempty content
|
||||
else flush $ go False mempty content)
|
||||
<> literal (getText close)
|
||||
go wrap attrs (CustomParent tag content) =
|
||||
char '<'
|
||||
<> fromChoiceString wrap tag
|
||||
<> attrs
|
||||
<> char '>'
|
||||
<> go wrap mempty content
|
||||
<> literal "</"
|
||||
<> fromChoiceString wrap tag
|
||||
<> char '>'
|
||||
go _wrap attrs (Leaf _ begin end _) =
|
||||
literal (getText begin)
|
||||
<> attrs
|
||||
<> literal (getText end)
|
||||
go wrap attrs (CustomLeaf tag close _) =
|
||||
char '<'
|
||||
<> fromChoiceString wrap tag
|
||||
<> attrs
|
||||
<> (if close then literal " />" else char '>')
|
||||
go wrap attrs (AddAttribute rawkey _ value h) =
|
||||
go wrap
|
||||
(space' wrap
|
||||
<> literal (getText rawkey)
|
||||
<> char '='
|
||||
<> doubleQuotes (fromChoiceString wrap value)
|
||||
<> attrs) h
|
||||
go wrap attrs (AddCustomAttribute key value h) =
|
||||
go wrap
|
||||
(space' wrap
|
||||
<> fromChoiceString wrap key
|
||||
<> char '='
|
||||
<> doubleQuotes (fromChoiceString wrap value)
|
||||
<> attrs) h
|
||||
go wrap _ (Content content _) = fromChoiceString wrap content
|
||||
go wrap _ (Comment comment _) =
|
||||
literal "<!--"
|
||||
<> space' wrap
|
||||
<> fromChoiceString wrap comment
|
||||
<> space' wrap
|
||||
<> "-->"
|
||||
go wrap attrs (Append h1 h2) = go wrap attrs h1 <> go wrap attrs h2
|
||||
go _ _ (Empty _) = mempty
|
||||
space' wrap = if wrap then space else char ' '
|
||||
|
||||
allowsWrap :: T.Text -> Bool
|
||||
allowsWrap t =
|
||||
not (t == "<pre" || t == "<style" || t == "<script" || t == "<textarea")
|
||||
|
||||
fromChoiceString :: Bool -- ^ Allow wrapping
|
||||
-> ChoiceString -- ^ String to render
|
||||
-> Doc Text -- ^ Resulting builder
|
||||
fromChoiceString wrap (Static s) = withWrap wrap $ getText s
|
||||
fromChoiceString wrap (String s) = withWrap wrap $
|
||||
escapeMarkupEntities $ T.pack s
|
||||
fromChoiceString wrap (Text s) = withWrap wrap $ escapeMarkupEntities s
|
||||
fromChoiceString wrap (ByteString s) = withWrap wrap $ decodeUtf8 s
|
||||
fromChoiceString _wrap (PreEscaped x) = -- don't wrap!
|
||||
case x of
|
||||
String s -> literal $ T.pack s
|
||||
Text s -> literal s
|
||||
s -> fromChoiceString False s
|
||||
fromChoiceString wrap (External x) = case x of
|
||||
-- Check that the sequence "</" is *not* in the external data.
|
||||
String s -> if "</" `isInfixOf` s then mempty else withWrap wrap (T.pack s)
|
||||
Text s -> if "</" `T.isInfixOf` s then mempty else withWrap wrap s
|
||||
ByteString s -> if "</" `S.isInfixOf` s then mempty else withWrap wrap (decodeUtf8 s)
|
||||
s -> fromChoiceString wrap s
|
||||
fromChoiceString wrap (AppendChoiceString x y) =
|
||||
fromChoiceString wrap x <> fromChoiceString wrap y
|
||||
fromChoiceString _ EmptyChoiceString = mempty
|
||||
|
||||
withWrap :: Bool -> Text -> Doc Text
|
||||
withWrap wrap
|
||||
| wrap = mconcat . toChunks
|
||||
| otherwise = literal
|
||||
|
||||
toChunks :: Text -> [Doc Text]
|
||||
toChunks = map toDoc . T.groupBy sameStatus
|
||||
where
|
||||
toDoc t =
|
||||
if T.any (== ' ') t
|
||||
then space
|
||||
else if T.any (== '\n') t
|
||||
then cr
|
||||
else literal t
|
||||
sameStatus c d =
|
||||
(c == ' ' && d == ' ') ||
|
||||
(c == '\n' && d == '\n') ||
|
||||
(c /= ' ' && d /= ' ' && c /= '\n' && d /= '\n')
|
||||
|
||||
|
||||
-- | Escape predefined XML entities in a text value
|
||||
--
|
||||
escapeMarkupEntities :: Text -- ^ Text to escape
|
||||
-> Text -- ^ Resulting Doc
|
||||
escapeMarkupEntities = T.concatMap escape
|
||||
where
|
||||
escape :: Char -> Text
|
||||
escape '<' = "<"
|
||||
escape '>' = ">"
|
||||
escape '&' = "&"
|
||||
escape '"' = """
|
||||
escape '\'' = "'"
|
||||
escape x = T.singleton x
|
|
@ -39,7 +39,7 @@ import qualified Data.Text as T
|
|||
import qualified Data.Text.Lazy as TL
|
||||
import Network.URI (URI (..), parseURIReference)
|
||||
import Numeric (showHex)
|
||||
import Text.DocLayout (render, literal)
|
||||
import Text.DocLayout (render, literal, Doc)
|
||||
import Text.Blaze.Internal (MarkupM (Empty), customLeaf, customParent)
|
||||
import Text.DocTemplates (FromContext (lookupContext), Context (..))
|
||||
import Text.Blaze.Html hiding (contents)
|
||||
|
@ -70,6 +70,7 @@ import Text.Pandoc.Class.PandocPure (runPure)
|
|||
import Text.Pandoc.Error
|
||||
import Text.Pandoc.Logging
|
||||
import Text.Pandoc.MIME (mediaCategory)
|
||||
import Text.Pandoc.Writers.Blaze (layoutMarkup)
|
||||
import Text.TeXMath
|
||||
import Text.XML.Light (elChildren, unode, unqual)
|
||||
import qualified Text.XML.Light as XML
|
||||
|
@ -160,7 +161,8 @@ writeHtmlStringForEPUB :: PandocMonad m
|
|||
-> m Text
|
||||
writeHtmlStringForEPUB version o = writeHtmlString'
|
||||
defaultWriterState{ stHtml5 = version == EPUB3,
|
||||
stEPUBVersion = Just version } o
|
||||
stEPUBVersion = Just version }
|
||||
o{ writerWrapText = WrapNone }
|
||||
|
||||
-- | Convert Pandoc document to Reveal JS HTML slide show.
|
||||
writeRevealJs :: PandocMonad m
|
||||
|
@ -207,17 +209,23 @@ writeHtmlString' :: PandocMonad m
|
|||
=> WriterState -> WriterOptions -> Pandoc -> m Text
|
||||
writeHtmlString' st opts d = do
|
||||
(body, context) <- evalStateT (pandocToHtml opts d) st
|
||||
let colwidth = case writerWrapText opts of
|
||||
WrapAuto -> Just (writerColumns opts)
|
||||
_ -> Nothing
|
||||
(if writerPreferAscii opts
|
||||
then toEntities
|
||||
else id) <$>
|
||||
case writerTemplate opts of
|
||||
Nothing -> return $ renderHtml' body
|
||||
Nothing -> return $
|
||||
case colwidth of
|
||||
Nothing -> renderHtml' body -- optimization, skip layout
|
||||
Just cols -> render (Just cols) $ layoutMarkup body
|
||||
Just tpl -> do
|
||||
-- warn if empty lang
|
||||
when (isNothing (getField "lang" context :: Maybe Text)) $
|
||||
report NoLangSpecified
|
||||
-- check for empty pagetitle
|
||||
context' <-
|
||||
(context' :: Context Text) <-
|
||||
case getField "pagetitle" context of
|
||||
Just (s :: Text) | not (T.null s) -> return context
|
||||
_ -> do
|
||||
|
@ -228,9 +236,9 @@ writeHtmlString' st opts d = do
|
|||
Just [] -> "Untitled"
|
||||
Just (x:_) -> takeBaseName $ T.unpack x
|
||||
report $ NoTitleElement fallback
|
||||
return $ resetField "pagetitle" fallback context
|
||||
return $ render Nothing $ renderTemplate tpl
|
||||
(defField "body" (renderHtml' body) context')
|
||||
return $ resetField "pagetitle" (literal fallback) context
|
||||
return $ render colwidth $ renderTemplate tpl
|
||||
(defField "body" (layoutMarkup body) context')
|
||||
|
||||
writeHtml' :: PandocMonad m => WriterState -> WriterOptions -> Pandoc -> m Html
|
||||
writeHtml' st opts d =
|
||||
|
@ -252,13 +260,13 @@ pandocToHtml opts (Pandoc meta blocks) = do
|
|||
let slideLevel = fromMaybe (getSlideLevel blocks) $ writerSlideLevel opts
|
||||
modify $ \st -> st{ stSlideLevel = slideLevel }
|
||||
metadata <- metaToContext opts
|
||||
(fmap (literal . renderHtml') . blockListToHtml opts)
|
||||
(fmap (literal . renderHtml') . inlineListToHtml opts)
|
||||
(fmap layoutMarkup . blockListToHtml opts)
|
||||
(fmap layoutMarkup . inlineListToHtml opts)
|
||||
meta
|
||||
let stringifyHTML = escapeStringForXML . stringify
|
||||
let authsMeta = map stringifyHTML $ docAuthors meta
|
||||
let authsMeta = map (literal . stringifyHTML) $ docAuthors meta
|
||||
let dateMeta = stringifyHTML $ docDate meta
|
||||
let descriptionMeta = escapeStringForXML $
|
||||
let descriptionMeta = literal $ escapeStringForXML $
|
||||
lookupMetaString "description" meta
|
||||
slideVariant <- gets stSlideVariant
|
||||
let sects = adjustNumbers opts $
|
||||
|
@ -267,7 +275,7 @@ pandocToHtml opts (Pandoc meta blocks) = do
|
|||
then blocks
|
||||
else prepSlides slideLevel blocks
|
||||
toc <- if writerTableOfContents opts && slideVariant /= S5Slides
|
||||
then fmap renderHtml' <$> tableOfContents opts sects
|
||||
then fmap layoutMarkup <$> tableOfContents opts sects
|
||||
else return Nothing
|
||||
blocks' <- blockListToHtml opts sects
|
||||
notes <- do
|
||||
|
@ -281,7 +289,7 @@ pandocToHtml opts (Pandoc meta blocks) = do
|
|||
return notes
|
||||
st <- get
|
||||
let thebody = blocks' >> notes
|
||||
let math = case writerHTMLMathMethod opts of
|
||||
let math = layoutMarkup $ case writerHTMLMathMethod opts of
|
||||
MathJax url
|
||||
| slideVariant /= RevealJsSlides ->
|
||||
-- mathjax is handled via a special plugin in revealjs
|
||||
|
@ -298,7 +306,7 @@ pandocToHtml opts (Pandoc meta blocks) = do
|
|||
nl opts
|
||||
let katexFlushLeft =
|
||||
case lookupContext "classoption" metadata of
|
||||
Just clsops | "fleqn" `elem` (clsops :: [Text]) -> "true"
|
||||
Just clsops | "fleqn" `elem` (clsops :: [Doc Text]) -> "true"
|
||||
_ -> "false"
|
||||
H.script $ text $ T.unlines [
|
||||
"document.addEventListener(\"DOMContentLoaded\", function () {"
|
||||
|
@ -324,15 +332,16 @@ pandocToHtml opts (Pandoc meta blocks) = do
|
|||
Just s | not (stHtml5 st) ->
|
||||
H.script ! A.type_ "text/javascript"
|
||||
$ preEscapedString
|
||||
("/*<![CDATA[*/\n" ++ T.unpack s ++
|
||||
("/*<![CDATA[*/\n" <> T.unpack s <>
|
||||
"/*]]>*/\n")
|
||||
| otherwise -> mempty
|
||||
Nothing -> mempty
|
||||
let mCss :: Maybe [Text] = lookupContext "css" metadata
|
||||
let context = (if stHighlighting st
|
||||
let context :: Context Text
|
||||
context = (if stHighlighting st
|
||||
then case writerHighlightStyle opts of
|
||||
Just sty -> defField "highlighting-css"
|
||||
(T.pack $ styleToCss sty)
|
||||
(literal $ T.pack $ styleToCss sty)
|
||||
Nothing -> id
|
||||
else id) .
|
||||
(if stCsl st
|
||||
|
@ -342,15 +351,15 @@ pandocToHtml opts (Pandoc meta blocks) = do
|
|||
Just 0 -> id
|
||||
Just n ->
|
||||
defField "csl-entry-spacing"
|
||||
(tshow n <> "em"))
|
||||
(literal $ tshow n <> "em"))
|
||||
else id) .
|
||||
(if stMath st
|
||||
then defField "math" (renderHtml' math)
|
||||
then defField "math" math
|
||||
else id) .
|
||||
(case writerHTMLMathMethod opts of
|
||||
MathJax u -> defField "mathjax" True .
|
||||
defField "mathjaxurl"
|
||||
(T.takeWhile (/='?') u)
|
||||
(literal $ T.takeWhile (/='?') u)
|
||||
_ -> defField "mathjax" False) .
|
||||
(case writerHTMLMathMethod opts of
|
||||
PlainMath -> defField "displaymath-css" True
|
||||
|
@ -361,11 +370,12 @@ pandocToHtml opts (Pandoc meta blocks) = do
|
|||
-- template can't distinguish False/undefined
|
||||
defField "controls" True .
|
||||
defField "controlsTutorial" True .
|
||||
defField "controlsLayout" ("bottom-right" :: Text) .
|
||||
defField "controlsBackArrows" ("faded" :: Text) .
|
||||
defField "controlsLayout"
|
||||
("bottom-right" :: Doc Text) .
|
||||
defField "controlsBackArrows" ("faded" :: Doc Text) .
|
||||
defField "progress" True .
|
||||
defField "slideNumber" False .
|
||||
defField "showSlideNumber" ("all" :: Text) .
|
||||
defField "showSlideNumber" ("all" :: Doc Text) .
|
||||
defField "hashOneBasedIndex" False .
|
||||
defField "hash" True .
|
||||
defField "respondToHashChanges" True .
|
||||
|
@ -377,7 +387,7 @@ pandocToHtml opts (Pandoc meta blocks) = do
|
|||
defField "touch" True .
|
||||
defField "loop" False .
|
||||
defField "rtl" False .
|
||||
defField "navigationMode" ("default" :: Text) .
|
||||
defField "navigationMode" ("default" :: Doc Text) .
|
||||
defField "shuffle" False .
|
||||
defField "fragments" True .
|
||||
defField "fragmentInURL" True .
|
||||
|
@ -385,22 +395,22 @@ pandocToHtml opts (Pandoc meta blocks) = do
|
|||
defField "help" True .
|
||||
defField "pause" True .
|
||||
defField "showNotes" False .
|
||||
defField "autoPlayMedia" ("null" :: Text) .
|
||||
defField "preloadIframes" ("null" :: Text) .
|
||||
defField "autoSlide" ("0" :: Text) .
|
||||
defField "autoPlayMedia" ("null" :: Doc Text) .
|
||||
defField "preloadIframes" ("null" :: Doc Text) .
|
||||
defField "autoSlide" ("0" :: Doc Text) .
|
||||
defField "autoSlideStoppable" True .
|
||||
defField "autoSlideMethod" ("null" :: Text) .
|
||||
defField "defaultTiming" ("null" :: Text) .
|
||||
defField "autoSlideMethod" ("null" :: Doc Text) .
|
||||
defField "defaultTiming" ("null" :: Doc Text) .
|
||||
defField "mouseWheel" False .
|
||||
defField "display" ("block" :: Text) .
|
||||
defField "display" ("block" :: Doc Text) .
|
||||
defField "hideInactiveCursor" True .
|
||||
defField "hideCursorTime" ("5000" :: Text) .
|
||||
defField "hideCursorTime" ("5000" :: Doc Text) .
|
||||
defField "previewLinks" False .
|
||||
defField "transition" ("slide" :: Text) .
|
||||
defField "transitionSpeed" ("default" :: Text) .
|
||||
defField "backgroundTransition" ("fade" :: Text) .
|
||||
defField "viewDistance" ("3" :: Text) .
|
||||
defField "mobileViewDistance" ("2" :: Text)
|
||||
defField "transition" ("slide" :: Doc Text) .
|
||||
defField "transitionSpeed" ("default" :: Doc Text) .
|
||||
defField "backgroundTransition" ("fade" :: Doc Text) .
|
||||
defField "viewDistance" ("3" :: Doc Text) .
|
||||
defField "mobileViewDistance" ("2" :: Doc Text)
|
||||
else id) .
|
||||
defField "document-css" (isNothing mCss && slideVariant == NoSlides) .
|
||||
defField "quotes" (stQuotes st) .
|
||||
|
@ -410,18 +420,18 @@ pandocToHtml opts (Pandoc meta blocks) = do
|
|||
maybe id (defField "toc") toc .
|
||||
maybe id (defField "table-of-contents") toc .
|
||||
defField "author-meta" authsMeta .
|
||||
maybe id (defField "date-meta")
|
||||
maybe id (defField "date-meta" . literal)
|
||||
(normalizeDate dateMeta) .
|
||||
defField "description-meta" descriptionMeta .
|
||||
defField "pagetitle"
|
||||
(stringifyHTML . docTitle $ meta) .
|
||||
defField "idprefix" (writerIdentifierPrefix opts) .
|
||||
(literal . stringifyHTML . docTitle $ meta) .
|
||||
defField "idprefix" (literal $ writerIdentifierPrefix opts) .
|
||||
-- these should maybe be set in pandoc.hs
|
||||
defField "slidy-url"
|
||||
("https://www.w3.org/Talks/Tools/Slidy2" :: Text) .
|
||||
defField "slideous-url" ("slideous" :: Text) .
|
||||
defField "revealjs-url" ("https://unpkg.com/reveal.js@^4/" :: Text) $
|
||||
defField "s5-url" ("s5/default" :: Text) .
|
||||
("https://www.w3.org/Talks/Tools/Slidy2" :: Doc Text) .
|
||||
defField "slideous-url" ("slideous" :: Doc Text) .
|
||||
defField "revealjs-url" ("https://unpkg.com/reveal.js@^4/" :: Doc Text) $
|
||||
defField "s5-url" ("s5/default" :: Doc Text) .
|
||||
defField "html5" (stHtml5 st) $
|
||||
metadata
|
||||
return (thebody, context)
|
||||
|
@ -705,12 +715,11 @@ figure opts attr@(_, _, attrList) txt (s,tit) = do
|
|||
img <- inlineToHtml opts (Image attr alt (s,tit))
|
||||
capt <- if null txt
|
||||
then return mempty
|
||||
else tocapt `fmap` inlineListToHtml opts txt
|
||||
else (nl opts <>) . tocapt <$> inlineListToHtml opts txt
|
||||
let inner = mconcat [nl opts, img, capt, nl opts]
|
||||
return $ if html5
|
||||
then H5.figure $ mconcat
|
||||
[nl opts, img, capt, nl opts]
|
||||
else H.div ! A.class_ "figure" $ mconcat
|
||||
[nl opts, img, nl opts, capt, nl opts]
|
||||
then H5.figure inner
|
||||
else H.div ! A.class_ "figure" $ inner
|
||||
|
||||
|
||||
adjustNumbers :: WriterOptions -> [Block] -> [Block]
|
||||
|
@ -1332,7 +1341,7 @@ inlineToHtml opts inline = do
|
|||
Space -> return $ strToHtml " "
|
||||
SoftBreak -> return $ case writerWrapText opts of
|
||||
WrapNone -> preEscapedText " "
|
||||
WrapAuto -> preEscapedText " "
|
||||
WrapAuto -> " "
|
||||
WrapPreserve -> preEscapedText "\n"
|
||||
LineBreak -> return $ do
|
||||
if html5 then H5.br else H.br
|
||||
|
|
|
@ -5,7 +5,8 @@
|
|||
.. _hello:
|
||||
.. _goodbye: example.com
|
||||
^D
|
||||
<p><a href="example.com">hello</a> and <a href="example.com">goodbye</a></p>
|
||||
<p><a href="example.com">hello</a> and <a
|
||||
href="example.com">goodbye</a></p>
|
||||
```
|
||||
|
||||
```
|
||||
|
|
|
@ -90,17 +90,20 @@
|
|||
<tbody>
|
||||
<tr class="odd">
|
||||
<td><p>1</p></td>
|
||||
<td><p><a href="Sébastien_Loeb" title="wikilink">Sébastien Loeb</a></p></td>
|
||||
<td><p><a href="Sébastien_Loeb" title="wikilink">Sébastien
|
||||
Loeb</a></p></td>
|
||||
<td><p>78</p></td>
|
||||
</tr>
|
||||
<tr class="even">
|
||||
<td><p>2</p></td>
|
||||
<td><p><strong><a href="Sébastien_Ogier" title="wikilink">Sébastien Ogier</a></strong></p></td>
|
||||
<td><p><strong><a href="Sébastien_Ogier" title="wikilink">Sébastien
|
||||
Ogier</a></strong></p></td>
|
||||
<td><p>38</p></td>
|
||||
</tr>
|
||||
<tr class="odd">
|
||||
<td><p>10</p></td>
|
||||
<td><p><a href="Hannu_Mikkola" title="wikilink">Hannu Mikkola</a></p></td>
|
||||
<td><p><a href="Hannu_Mikkola" title="wikilink">Hannu
|
||||
Mikkola</a></p></td>
|
||||
<td><p>18</p></td>
|
||||
</tr>
|
||||
</tbody>
|
||||
|
|
|
@ -19,8 +19,12 @@
|
|||
\end{document}
|
||||
^D
|
||||
<div class="epigraph">
|
||||
<p>Das Recht hat kein Dasein f<span>ü</span>r sich, sein Wesen vielmehr ist das Leben des Menschen selbst, von einer besonderen Seite angesehen.</p>
|
||||
<p>Das Recht hat kein Dasein f<span>ü</span>r sich, sein Wesen vielmehr ist das Leben des Menschen selbst, von einer besonderen Seite angesehen.</p>
|
||||
<p>Das Recht hat kein Dasein f<span>ü</span>r sich, sein Wesen vielmehr
|
||||
ist das Leben des Menschen selbst, von einer besonderen Seite
|
||||
angesehen.</p>
|
||||
<p>Das Recht hat kein Dasein f<span>ü</span>r sich, sein Wesen vielmehr
|
||||
ist das Leben des Menschen selbst, von einer besonderen Seite
|
||||
angesehen.</p>
|
||||
<ul>
|
||||
<li><p>hey</p></li>
|
||||
<li><p>hey</p></li>
|
||||
|
|
|
@ -2,7 +2,9 @@
|
|||
% pandoc -f latex -t html
|
||||
I want to explain the interface of \lstinline[language=Java]{public class MyClass}.
|
||||
^D
|
||||
<p>I want to explain the interface of <code class="sourceCode java"><span class="kw">public</span> <span class="kw">class</span> MyClass</code>.</p>
|
||||
<p>I want to explain the interface of <code class="sourceCode
|
||||
java"><span class="kw">public</span> <span class="kw">class</span>
|
||||
MyClass</code>.</p>
|
||||
|
||||
```
|
||||
|
||||
|
@ -10,7 +12,8 @@ I want to explain the interface of \lstinline[language=Java]{public class MyClas
|
|||
% pandoc -f latex -t html
|
||||
I want to explain the interface of \lstinline{public class MyClass}.
|
||||
^D
|
||||
<p>I want to explain the interface of <code>public class MyClass</code>.</p>
|
||||
<p>I want to explain the interface of <code>public class
|
||||
MyClass</code>.</p>
|
||||
|
||||
```
|
||||
|
||||
|
@ -43,7 +46,9 @@ I want to explain the interface of \lstinline[language=Java]{public class MyClas
|
|||
% pandoc -f latex -t html
|
||||
I want to explain the interface of \mintinline{java}{public class MyClass}.
|
||||
^D
|
||||
<p>I want to explain the interface of <code class="sourceCode java"><span class="kw">public</span> <span class="kw">class</span> MyClass</code>.</p>
|
||||
<p>I want to explain the interface of <code class="sourceCode
|
||||
java"><span class="kw">public</span> <span class="kw">class</span>
|
||||
MyClass</code>.</p>
|
||||
|
||||
```
|
||||
|
||||
|
@ -51,7 +56,9 @@ I want to explain the interface of \mintinline{java}{public class MyClass}.
|
|||
% pandoc -f latex -t html
|
||||
I want to explain the interface of \mintinline{java}|public class MyClass|.
|
||||
^D
|
||||
<p>I want to explain the interface of <code class="sourceCode java"><span class="kw">public</span> <span class="kw">class</span> MyClass</code>.</p>
|
||||
<p>I want to explain the interface of <code class="sourceCode
|
||||
java"><span class="kw">public</span> <span class="kw">class</span>
|
||||
MyClass</code>.</p>
|
||||
|
||||
```
|
||||
|
||||
|
|
|
@ -16,10 +16,12 @@
|
|||
\end{figure}
|
||||
^D
|
||||
<figure>
|
||||
<img src="img1.jpg" alt="Caption 1" /><figcaption aria-hidden="true">Caption 1</figcaption>
|
||||
<img src="img1.jpg" alt="Caption 1" />
|
||||
<figcaption aria-hidden="true">Caption 1</figcaption>
|
||||
</figure>
|
||||
<figure>
|
||||
<img src="img2.jpg" alt="Caption 2" /><figcaption aria-hidden="true">Caption 2</figcaption>
|
||||
<img src="img2.jpg" alt="Caption 2" />
|
||||
<figcaption aria-hidden="true">Caption 2</figcaption>
|
||||
</figure>
|
||||
```
|
||||
```
|
||||
|
@ -30,6 +32,7 @@
|
|||
\end{figure}
|
||||
^D
|
||||
<figure>
|
||||
<img src="img1.jpg" alt="Caption 3" /><figcaption aria-hidden="true">Caption 3</figcaption>
|
||||
<img src="img1.jpg" alt="Caption 3" />
|
||||
<figcaption aria-hidden="true">Caption 3</figcaption>
|
||||
</figure>
|
||||
```
|
||||
|
|
|
@ -55,6 +55,7 @@
|
|||
^D
|
||||
<p><a href="u">a</a></p>
|
||||
<p><a href="u">a</a></p>
|
||||
<p><a href="u2">a</a> <a href="u">A</a> <a href="u" class="foo">a</a></p>
|
||||
<p><a href="u2">a</a> <a href="u">A</a> <a href="u"
|
||||
class="foo">a</a></p>
|
||||
<p><a href="u3">a</a></p>
|
||||
```
|
||||
|
|
|
@ -32,11 +32,14 @@ A spider: [spider]
|
|||
^D
|
||||
<h1 id="chapter-one">Chapter one</h1>
|
||||
<p>A spider: <img src="command/chap1/spider.png" alt="spider" /></p>
|
||||
<p>Another spider: <img src="command/chap2/spider.png" alt="another spider" /></p>
|
||||
<p>Another spider: <img src="command/chap2/spider.png" alt="another
|
||||
spider" /></p>
|
||||
<p>The moon: <img src="command/chap1/../../lalune.jpg" alt="moon" /></p>
|
||||
<p>Link to <a href="command/chap1/spider.png">spider picture</a>.</p>
|
||||
<p>URL left alone: <a href="https://pandoc.org/MANUAL.html">manual</a>.</p>
|
||||
<p>Absolute path left alone: <a href="/foo/bar/baz.png">absolute</a>.</p>
|
||||
<p>URL left alone: <a
|
||||
href="https://pandoc.org/MANUAL.html">manual</a>.</p>
|
||||
<p>Absolute path left alone: <a
|
||||
href="/foo/bar/baz.png">absolute</a>.</p>
|
||||
<p>Link to fragment: <a href="#chapter-two">chapter two</a>.</p>
|
||||
<p>Empty path: <a href="">empty</a>.</p>
|
||||
<h1 id="chapter-two">Chapter two</h1>
|
||||
|
@ -48,11 +51,14 @@ A spider: [spider]
|
|||
^D
|
||||
<h1>Chapter one</h1>
|
||||
<p>A spider: <img src="command/chap1/spider.png" alt="spider" /></p>
|
||||
<p>Another spider: <img src="command/chap2/spider.png" alt="another spider" /></p>
|
||||
<p>Another spider: <img src="command/chap2/spider.png" alt="another
|
||||
spider" /></p>
|
||||
<p>The moon: <img src="command/chap1/../../lalune.jpg" alt="moon" /></p>
|
||||
<p>Link to <a href="command/chap1/spider.png">spider picture</a>.</p>
|
||||
<p>URL left alone: <a href="https://pandoc.org/MANUAL.html">manual</a>.</p>
|
||||
<p>Absolute path left alone: <a href="/foo/bar/baz.png">absolute</a>.</p>
|
||||
<p>URL left alone: <a
|
||||
href="https://pandoc.org/MANUAL.html">manual</a>.</p>
|
||||
<p>Absolute path left alone: <a
|
||||
href="/foo/bar/baz.png">absolute</a>.</p>
|
||||
<p>Link to fragment: <a href="#chapter-two">chapter two</a>.</p>
|
||||
<p>Empty path: <a href="">empty</a>.</p>
|
||||
<h1>Chapter two</h1>
|
||||
|
|
|
@ -2,7 +2,8 @@
|
|||
% pandoc
|
||||
[@Alhazen1572-qk, V.9]: "competentius est"
|
||||
^D
|
||||
<p><span class="citation" data-cites="Alhazen1572-qk">[@Alhazen1572-qk, V.9]</span>: “competentius est”</p>
|
||||
<p><span class="citation" data-cites="Alhazen1572-qk">[@Alhazen1572-qk,
|
||||
V.9]</span>: “competentius est”</p>
|
||||
```
|
||||
|
||||
```
|
||||
|
|
|
@ -4,5 +4,6 @@
|
|||
|
||||
[image]: http://example.com/image.jpg {height=35mm}
|
||||
^D
|
||||
<p><img src="http://example.com/image.jpg" style="height:35mm" alt="image" /></p>
|
||||
<p><img src="http://example.com/image.jpg" style="height:35mm"
|
||||
alt="image" /></p>
|
||||
```
|
||||
|
|
|
@ -57,7 +57,8 @@ Outside all lists.
|
|||
</ul>
|
||||
<pre id="carrie" class="example"><code>This belongs to the outer list element, and is aligned accordingly, since the NAME attribute is not indented deeply enough. It is not enough for the BEGIN alone to be aligned deeply if the block is meant to have a NAME.
|
||||
</code></pre>
|
||||
<p>Still in the shallower list element since the preceding example block forced the deeper list element to terminate.</p></li>
|
||||
<p>Still in the shallower list element since the preceding example block
|
||||
forced the deeper list element to terminate.</p></li>
|
||||
</ul>
|
||||
<p>Outside all lists.</p>
|
||||
```
|
||||
|
|
|
@ -2,11 +2,15 @@
|
|||
% pandoc --id-prefix=foo
|
||||
This.^[Has a footnote.]
|
||||
^D
|
||||
<p>This.<a href="#foofn1" class="footnote-ref" id="foofnref1" role="doc-noteref"><sup>1</sup></a></p>
|
||||
<section class="footnotes footnotes-end-of-document" role="doc-endnotes">
|
||||
<p>This.<a href="#foofn1" class="footnote-ref" id="foofnref1"
|
||||
role="doc-noteref"><sup>1</sup></a></p>
|
||||
<section class="footnotes footnotes-end-of-document"
|
||||
role="doc-endnotes">
|
||||
<hr />
|
||||
<ol>
|
||||
<li id="foofn1" role="doc-endnote"><p>Has a footnote.<a href="#foofnref1" class="footnote-back" role="doc-backlink">↩︎</a></p></li>
|
||||
<li id="foofn1" role="doc-endnote"><p>Has a footnote.<a
|
||||
href="#foofnref1" class="footnote-back"
|
||||
role="doc-backlink">↩︎</a></p></li>
|
||||
</ol>
|
||||
</section>
|
||||
```
|
||||
|
|
|
@ -5,6 +5,6 @@
|
|||
\end{equation}
|
||||
^D
|
||||
<p><span class="math display">\[\begin{equation}
|
||||
E=mc^2
|
||||
E=mc^2
|
||||
\end{equation}\]</span></p>
|
||||
```
|
||||
|
|
|
@ -3,6 +3,7 @@
|
|||
![Caption](img.png){#img:1}
|
||||
^D
|
||||
<figure>
|
||||
<img src="img.png" id="img:1" alt="Caption" /><figcaption aria-hidden="true">Caption</figcaption>
|
||||
<img src="img.png" id="img:1" alt="Caption" />
|
||||
<figcaption aria-hidden="true">Caption</figcaption>
|
||||
</figure>
|
||||
```
|
||||
|
|
|
@ -41,5 +41,7 @@ My:thumbsup:emoji:heart:
|
|||
My:thumbsup:emoji:heart:x :hearts: xyz
|
||||
^D
|
||||
<h1><span class="emoji" data-emoji="zero">0️⃣</span> header</h1>
|
||||
<p>My<span class="emoji" data-emoji="thumbsup">👍</span>emoji<span class="emoji" data-emoji="heart">❤️</span>x <span class="emoji" data-emoji="hearts">♥️</span> xyz</p>
|
||||
<p>My<span class="emoji" data-emoji="thumbsup">👍</span>emoji<span
|
||||
class="emoji" data-emoji="heart">❤️</span>x <span class="emoji"
|
||||
data-emoji="hearts">♥️</span> xyz</p>
|
||||
```
|
||||
|
|
|
@ -8,7 +8,8 @@
|
|||
__ link1_
|
||||
__ link2_
|
||||
^D
|
||||
<p><a href="http://www.example.com/">click here</a> or <a href="http://johnmacfarlane.net/pandoc/">click here</a></p>
|
||||
<p><a href="http://www.example.com/">click here</a> or <a
|
||||
href="http://johnmacfarlane.net/pandoc/">click here</a></p>
|
||||
```
|
||||
|
||||
Multiple indirection:
|
||||
|
|
|
@ -5,7 +5,8 @@
|
|||
## Header 2
|
||||
^D
|
||||
<figure>
|
||||
<img src="./my-figure.jpg" width="500" alt="My caption" /><figcaption aria-hidden="true">My caption</figcaption>
|
||||
<img src="./my-figure.jpg" width="500" alt="My caption" />
|
||||
<figcaption aria-hidden="true">My caption</figcaption>
|
||||
</figure>
|
||||
|
||||
## Header 2
|
||||
|
|
|
@ -20,8 +20,10 @@ Something
|
|||
<li>Two <code>-->something<!--</code></li>
|
||||
<li>Three</li>
|
||||
</ol>
|
||||
<div class="sourceCode" id="cb1"><pre class="sourceCode html"><code class="sourceCode html"><span id="cb1-1"><a href="#cb1-1" aria-hidden="true" tabindex="-1"></a>--><span class="co"><!--<script>alert('Escaped!')</script></span></span></code></pre></div>
|
||||
<div class="sourceCode" id="cb2"><pre class="sourceCode html"><code class="sourceCode html"><span id="cb2-1"><a href="#cb2-1" aria-hidden="true" tabindex="-1"></a>Something</span></code></pre></div>
|
||||
<div class="sourceCode" id="cb1"><pre class="sourceCode
|
||||
html"><code class="sourceCode html"><span id="cb1-1"><a href="#cb1-1" aria-hidden="true" tabindex="-1"></a>--><span class="co"><!--<script>alert('Escaped!')</script></span></span></code></pre></div>
|
||||
<div class="sourceCode" id="cb2"><pre class="sourceCode
|
||||
html"><code class="sourceCode html"><span id="cb2-1"><a href="#cb2-1" aria-hidden="true" tabindex="-1"></a>Something</span></code></pre></div>
|
||||
```
|
||||
|
||||
```
|
||||
|
@ -46,8 +48,10 @@ Something
|
|||
<li><code>-->something<!--</code></li>
|
||||
<li>bye <code>-->something else<!--</code></li>
|
||||
</ul>
|
||||
<div class="sourceCode" id="cb1"><pre class="sourceCode html"><code class="sourceCode html"><span id="cb1-1"><a href="#cb1-1" aria-hidden="true" tabindex="-1"></a>--><span class="co"><!--<script>alert('Escaped!')</script></span></span></code></pre></div>
|
||||
<div class="sourceCode" id="cb2"><pre class="sourceCode html"><code class="sourceCode html"><span id="cb2-1"><a href="#cb2-1" aria-hidden="true" tabindex="-1"></a>Something</span></code></pre></div>
|
||||
<div class="sourceCode" id="cb1"><pre class="sourceCode
|
||||
html"><code class="sourceCode html"><span id="cb1-1"><a href="#cb1-1" aria-hidden="true" tabindex="-1"></a>--><span class="co"><!--<script>alert('Escaped!')</script></span></span></code></pre></div>
|
||||
<div class="sourceCode" id="cb2"><pre class="sourceCode
|
||||
html"><code class="sourceCode html"><span id="cb2-1"><a href="#cb2-1" aria-hidden="true" tabindex="-1"></a>Something</span></code></pre></div>
|
||||
```
|
||||
|
||||
```
|
||||
|
|
|
@ -3,6 +3,7 @@
|
|||
![test](foo){aria-describedby="barbaz"}
|
||||
^D
|
||||
<figure>
|
||||
<img src="foo" aria-describedby="barbaz" alt="test" /><figcaption aria-hidden="true">test</figcaption>
|
||||
<img src="foo" aria-describedby="barbaz" alt="test" />
|
||||
<figcaption aria-hidden="true">test</figcaption>
|
||||
</figure>
|
||||
```
|
||||
|
|
|
@ -5,7 +5,8 @@ a
|
|||
b
|
||||
```
|
||||
^D
|
||||
<div class="sourceCode" id="foocb1"><pre class="sourceCode haskell"><code class="sourceCode haskell"><span id="foocb1-1"><a href="#foocb1-1" aria-hidden="true" tabindex="-1"></a>a</span>
|
||||
<div class="sourceCode" id="foocb1"><pre class="sourceCode
|
||||
haskell"><code class="sourceCode haskell"><span id="foocb1-1"><a href="#foocb1-1" aria-hidden="true" tabindex="-1"></a>a</span>
|
||||
<span id="foocb1-2"><a href="#foocb1-2" aria-hidden="true" tabindex="-1"></a>b</span></code></pre></div>
|
||||
````
|
||||
|
||||
|
@ -16,7 +17,8 @@ a
|
|||
b
|
||||
```
|
||||
^D
|
||||
<div class="sourceCode" id="foobar"><pre class="sourceCode haskell"><code class="sourceCode haskell"><span id="foobar-1"><a href="#foobar-1" aria-hidden="true" tabindex="-1"></a>a</span>
|
||||
<div class="sourceCode" id="foobar"><pre class="sourceCode
|
||||
haskell"><code class="sourceCode haskell"><span id="foobar-1"><a href="#foobar-1" aria-hidden="true" tabindex="-1"></a>a</span>
|
||||
<span id="foobar-2"><a href="#foobar-2" aria-hidden="true" tabindex="-1"></a>b</span></code></pre></div>
|
||||
````
|
||||
|
||||
|
|
|
@ -2,13 +2,19 @@
|
|||
% pandoc --webtex
|
||||
$T_n={n+1 \choose 2}$
|
||||
^D
|
||||
<p><img style="vertical-align:middle" src="https://latex.codecogs.com/png.latex?%5Ctextstyle%20T_n%3D%7Bn%2B1%20%5Cchoose%202%7D" alt="T_n={n+1 \choose 2}" title="T_n={n+1 \choose 2}" class="math inline" /></p>
|
||||
<p><img style="vertical-align:middle"
|
||||
src="https://latex.codecogs.com/png.latex?%5Ctextstyle%20T_n%3D%7Bn%2B1%20%5Cchoose%202%7D"
|
||||
alt="T_n={n+1 \choose 2}" title="T_n={n+1 \choose 2}" class="math
|
||||
inline" /></p>
|
||||
````
|
||||
|
||||
````
|
||||
% pandoc --webtex
|
||||
$$T_n={n+1 \choose 2}$$
|
||||
^D
|
||||
<p><img style="vertical-align:middle" src="https://latex.codecogs.com/png.latex?%5Cdisplaystyle%20T_n%3D%7Bn%2B1%20%5Cchoose%202%7D" alt="T_n={n+1 \choose 2}" title="T_n={n+1 \choose 2}" class="math display" /></p>
|
||||
<p><img style="vertical-align:middle"
|
||||
src="https://latex.codecogs.com/png.latex?%5Cdisplaystyle%20T_n%3D%7Bn%2B1%20%5Cchoose%202%7D"
|
||||
alt="T_n={n+1 \choose 2}" title="T_n={n+1 \choose 2}" class="math
|
||||
display" /></p>
|
||||
````
|
||||
|
||||
|
|
|
@ -2,5 +2,6 @@
|
|||
% pandoc -f gfm
|
||||
### Jekyll Plugins & Gems :gem:
|
||||
^D
|
||||
<h3 id="jekyll-plugins--gems-gem">Jekyll Plugins & Gems <span class="emoji" data-emoji="gem">💎</span></h3>
|
||||
<h3 id="jekyll-plugins--gems-gem">Jekyll Plugins & Gems <span
|
||||
class="emoji" data-emoji="gem">💎</span></h3>
|
||||
```
|
||||
|
|
|
@ -6,7 +6,8 @@
|
|||
<p><span id="nav.xhtml"></span></p>
|
||||
<nav epub:type="landmarks" id="landmarks" hidden="hidden">
|
||||
<ol>
|
||||
<li><a href="text/title_page.xhtml" class="titlepage">Title Page</a></li>
|
||||
<li><a href="text/title_page.xhtml" class="titlepage">Title
|
||||
Page</a></li>
|
||||
<li><a href="#nav.xhtml#toc" class="toc">Table of Contents</a></li>
|
||||
</ol>
|
||||
</nav>
|
||||
|
|
|
@ -4,7 +4,8 @@
|
|||
* `--argA | --argB` This item has a pipe character
|
||||
^D
|
||||
<ul>
|
||||
<li><code>--argument</code> This item does not have a pipe character</li>
|
||||
<li><code>--argument</code> This item does not have a pipe
|
||||
character</li>
|
||||
<li><code>--argA | --argB</code> This item has a pipe character</li>
|
||||
</ul>
|
||||
```
|
||||
|
|
|
@ -6,13 +6,16 @@ Test.[^fn]
|
|||
|
||||
![Caption.](/image.jpg)
|
||||
^D
|
||||
<p>Test.<a href="#fn1" class="footnote-ref" id="fnref1" role="doc-noteref"><sup>1</sup></a></p>
|
||||
<section class="footnotes footnotes-end-of-document" role="doc-endnotes">
|
||||
<p>Test.<a href="#fn1" class="footnote-ref" id="fnref1"
|
||||
role="doc-noteref"><sup>1</sup></a></p>
|
||||
<section class="footnotes footnotes-end-of-document"
|
||||
role="doc-endnotes">
|
||||
<hr />
|
||||
<ol>
|
||||
<li id="fn1" role="doc-endnote"><p>Foo:</p>
|
||||
<figure>
|
||||
<img src="/image.jpg" alt="Caption." /><figcaption aria-hidden="true">Caption.</figcaption>
|
||||
<img src="/image.jpg" alt="Caption." />
|
||||
<figcaption aria-hidden="true">Caption.</figcaption>
|
||||
</figure>
|
||||
<a href="#fnref1" class="footnote-back" role="doc-backlink">↩︎</a></li>
|
||||
</ol>
|
||||
|
|
|
@ -4,7 +4,8 @@
|
|||
|
||||
^D
|
||||
<figure>
|
||||
<img src="../media/rId25.jpg" title="title" alt="alt" /><figcaption>caption</figcaption>
|
||||
<img src="../media/rId25.jpg" title="title" alt="alt" />
|
||||
<figcaption>caption</figcaption>
|
||||
</figure>
|
||||
```
|
||||
|
||||
|
@ -14,6 +15,7 @@
|
|||
|
||||
^D
|
||||
<figure>
|
||||
<img src="../media/rId25.jpg" title="title" alt="caption" /><figcaption aria-hidden="true">caption</figcaption>
|
||||
<img src="../media/rId25.jpg" title="title" alt="caption" />
|
||||
<figcaption aria-hidden="true">caption</figcaption>
|
||||
</figure>
|
||||
```
|
||||
|
|
|
@ -7,5 +7,10 @@ holds a useful spot.
|
|||
|
||||
.. _Labyrinth Lord\: Revised Edition: https://www.drivethrurpg.com/product/64332/Labyrinth-Lord-Revised-Edition
|
||||
^D
|
||||
<p>While <a href="https://www.drivethrurpg.com/product/64332/Labyrinth-Lord-Revised-Edition">Labyrinth Lord: Revised Edition</a> (LLRE; PDF and POD) has been criticized for not being a completely faithful retro-clone of the Moldvay/Cook/Marsh Basic/Expert D&D rules (B/X), I think it still holds a useful spot.</p>
|
||||
<p>While <a
|
||||
href="https://www.drivethrurpg.com/product/64332/Labyrinth-Lord-Revised-Edition">Labyrinth
|
||||
Lord: Revised Edition</a> (LLRE; PDF and POD) has been criticized for
|
||||
not being a completely faithful retro-clone of the Moldvay/Cook/Marsh
|
||||
Basic/Expert D&D rules (B/X), I think it still holds a useful
|
||||
spot.</p>
|
||||
```
|
||||
|
|
|
@ -21,7 +21,8 @@
|
|||
<tr class="odd">
|
||||
<td></td>
|
||||
<td></td>
|
||||
<td>cccccccccc cccccccccc cccccccccc cccccccccc cccccccccc cccccccccc</td>
|
||||
<td>cccccccccc cccccccccc cccccccccc cccccccccc cccccccccc
|
||||
cccccccccc</td>
|
||||
</tr>
|
||||
</tbody>
|
||||
</table>
|
||||
|
|
|
@ -7,11 +7,13 @@ Here is a citation reference: [CIT2002]_.
|
|||
.. [CIT2002] This is the citation. It's just like a footnote,
|
||||
except the label is textual.
|
||||
^D
|
||||
<p>Here is a citation reference: <a href="#CIT2002" class="citation">[CIT2002]</a>.</p>
|
||||
<p>Here is a citation reference: <a href="#CIT2002"
|
||||
class="citation">[CIT2002]</a>.</p>
|
||||
<div id="citations">
|
||||
<dl>
|
||||
<dt><span id="CIT2002" class="citation-label">CIT2002</span></dt>
|
||||
<dd><p>This is the citation. It's just like a footnote, except the label is textual.</p>
|
||||
<dd><p>This is the citation. It's just like a footnote, except the label
|
||||
is textual.</p>
|
||||
</dd>
|
||||
</dl>
|
||||
</div>
|
||||
|
|
|
@ -10,9 +10,13 @@
|
|||
|
||||
![](./test.jpg)
|
||||
^D
|
||||
<p><video src="./test.mp4" controls=""><a href="./test.mp4">Video</a></video></p>
|
||||
<p><video src="foo/test.webm" width="300" controls=""><a href="foo/test.webm">Your browser does not support video.</a></video></p>
|
||||
<p><audio src="test.mp3" controls=""><a href="test.mp3">Audio</a></audio></p>
|
||||
<p><video src="./test.mp4" controls=""><a
|
||||
href="./test.mp4">Video</a></video></p>
|
||||
<p><video src="foo/test.webm" width="300" controls=""><a
|
||||
href="foo/test.webm">Your browser does not support
|
||||
video.</a></video></p>
|
||||
<p><audio src="test.mp3" controls=""><a
|
||||
href="test.mp3">Audio</a></audio></p>
|
||||
<p><embed src="./test.pdf" /></p>
|
||||
<p><img src="./test.jpg" /></p>
|
||||
```
|
||||
|
|
|
@ -1,8 +1,12 @@
|
|||
<div id="5cf8f54d-bf3c-4db2-996d-22662a86ad43" class="cell code" data-execution_count="1">
|
||||
<div class="sourceCode" id="cb1"><pre class="sourceCode python"><code class="sourceCode python"><span id="cb1-1"><a href="#cb1-1" aria-hidden="true" tabindex="-1"></a><span class="im">import</span> matplotlib.pyplot <span class="im">as</span> plt</span></code></pre></div>
|
||||
<div id="5cf8f54d-bf3c-4db2-996d-22662a86ad43" class="cell code"
|
||||
data-execution_count="1">
|
||||
<div class="sourceCode" id="cb1"><pre class="sourceCode
|
||||
python"><code class="sourceCode python"><span id="cb1-1"><a href="#cb1-1" aria-hidden="true" tabindex="-1"></a><span class="im">import</span> matplotlib.pyplot <span class="im">as</span> plt</span></code></pre></div>
|
||||
</div>
|
||||
<div id="a0228622-9ff8-4392-9ddd-f70a90f0e106" class="cell code" data-execution_count="2">
|
||||
<div class="sourceCode" id="cb2"><pre class="sourceCode python"><code class="sourceCode python"><span id="cb2-1"><a href="#cb2-1" aria-hidden="true" tabindex="-1"></a>fig, ax <span class="op">=</span> plt.subplots(figsize<span class="op">=</span>(<span class="dv">1</span>, <span class="dv">1</span>), dpi<span class="op">=</span><span class="dv">4</span>)</span>
|
||||
<div id="a0228622-9ff8-4392-9ddd-f70a90f0e106" class="cell code"
|
||||
data-execution_count="2">
|
||||
<div class="sourceCode" id="cb2"><pre class="sourceCode
|
||||
python"><code class="sourceCode python"><span id="cb2-1"><a href="#cb2-1" aria-hidden="true" tabindex="-1"></a>fig, ax <span class="op">=</span> plt.subplots(figsize<span class="op">=</span>(<span class="dv">1</span>, <span class="dv">1</span>), dpi<span class="op">=</span><span class="dv">4</span>)</span>
|
||||
<span id="cb2-2"><a href="#cb2-2" aria-hidden="true" tabindex="-1"></a>ax.imshow([[<span class="dv">0</span>, <span class="dv">1</span>], [<span class="dv">2</span>, <span class="dv">3</span>]])<span class="op">;</span></span></code></pre></div>
|
||||
<div class="output display_data">
|
||||
<p><em>you should see this when converting from ipynb to html instead of the image below.</em></p>
|
||||
|
|
|
@ -56,7 +56,8 @@
|
|||
<div id="math" class="slide section level1">
|
||||
<h1>Math</h1>
|
||||
<ul>
|
||||
<li><span class="math inline">$\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}$</span></li>
|
||||
<li><span class="math inline">$\frac{d}{dx}f(x)=\lim_{h\to
|
||||
0}\frac{f(x+h)-f(x)}{h}$</span></li>
|
||||
</ul>
|
||||
</div>
|
||||
</div>
|
||||
|
|
|
@ -28,7 +28,9 @@
|
|||
<link rel="stylesheet" href="s5/default/opera.css" type="text/css" media="projection" id="operaFix" />
|
||||
<!-- S5 JS -->
|
||||
<script src="s5/default/slides.js" type="text/javascript"></script>
|
||||
<script src="https://cdn.jsdelivr.net/npm/mathjax@3/es5/tex-chtml-full.js" type="text/javascript"></script>
|
||||
<script
|
||||
src="https://cdn.jsdelivr.net/npm/mathjax@3/es5/tex-chtml-full.js"
|
||||
type="text/javascript"></script>
|
||||
</head>
|
||||
<body>
|
||||
<div class="layout">
|
||||
|
@ -56,7 +58,8 @@
|
|||
<div id="math" class="slide section level1">
|
||||
<h1>Math</h1>
|
||||
<ul class="incremental">
|
||||
<li><span class="math inline">\(\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}\)</span></li>
|
||||
<li><span class="math inline">\(\frac{d}{dx}f(x)=\lim_{h\to
|
||||
0}\frac{f(x+h)-f(x)}{h}\)</span></li>
|
||||
</ul>
|
||||
</div>
|
||||
</div>
|
||||
|
|
|
@ -5,5 +5,6 @@
|
|||
</ul>
|
||||
<h1 id="math">Math</h1>
|
||||
<ul>
|
||||
<li><span class="math inline">$\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}$</span></li>
|
||||
<li><span class="math inline">$\frac{d}{dx}f(x)=\lim_{h\to
|
||||
0}\frac{f(x+h)-f(x)}{h}$</span></li>
|
||||
</ul>
|
||||
|
|
|
@ -35,7 +35,8 @@ STUFF INSERTED
|
|||
</ul>
|
||||
<h1 id="math">Math</h1>
|
||||
<ul>
|
||||
<li><span class="math inline">$\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}$</span></li>
|
||||
<li><span class="math inline">$\frac{d}{dx}f(x)=\lim_{h\to
|
||||
0}\frac{f(x+h)-f(x)}{h}$</span></li>
|
||||
</ul>
|
||||
STUFF INSERTED
|
||||
</body>
|
||||
|
|
|
@ -121,7 +121,8 @@
|
|||
<td style="text-align: center;">Second</td>
|
||||
<td style="text-align: left;">row</td>
|
||||
<td style="text-align: right;">5.0</td>
|
||||
<td style="text-align: left;">Here’s another one. Note the blank line between rows.</td>
|
||||
<td style="text-align: left;">Here’s another one. Note the blank line between
|
||||
rows.</td>
|
||||
</tr>
|
||||
</tbody>
|
||||
</table>
|
||||
|
@ -152,7 +153,8 @@
|
|||
<td style="text-align: center;">Second</td>
|
||||
<td style="text-align: left;">row</td>
|
||||
<td style="text-align: right;">5.0</td>
|
||||
<td style="text-align: left;">Here’s another one. Note the blank line between rows.</td>
|
||||
<td style="text-align: left;">Here’s another one. Note the blank line between
|
||||
rows.</td>
|
||||
</tr>
|
||||
</tbody>
|
||||
</table>
|
||||
|
|
|
@ -156,10 +156,12 @@
|
|||
<h2 class="author">Anonymous</h2>
|
||||
<h3 class="date">July 17, 2006</h3>
|
||||
</div>
|
||||
<p>This is a set of tests for pandoc. Most of them are adapted from John Gruber’s markdown test suite.</p>
|
||||
<p>This is a set of tests for pandoc. Most of them are adapted from John
|
||||
Gruber’s markdown test suite.</p>
|
||||
<hr />
|
||||
<h1 id="headers">Headers</h1>
|
||||
<h2 id="level-2-with-an-embedded-link">Level 2 with an <a href="/url">embedded link</a></h2>
|
||||
<h2 id="level-2-with-an-embedded-link">Level 2 with an <a href="/url">embedded
|
||||
link</a></h2>
|
||||
<h3 id="level-3-with-emphasis">Level 3 with <em>emphasis</em></h3>
|
||||
<h4 id="level-4">Level 4</h4>
|
||||
<h5 id="level-5">Level 5</h5>
|
||||
|
@ -172,7 +174,9 @@
|
|||
<hr />
|
||||
<h1 id="paragraphs">Paragraphs</h1>
|
||||
<p>Here’s a regular paragraph.</p>
|
||||
<p>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.</p>
|
||||
<p>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.</p>
|
||||
<p>Here’s one with a bullet. * criminey.</p>
|
||||
<p>There should be a hard line break<br />
|
||||
here.</p>
|
||||
|
@ -283,7 +287,8 @@ These should not be escaped: \$ \\ \> \[ \{</code></pre>
|
|||
<p>Multiple paragraphs:</p>
|
||||
<ol style="list-style-type: decimal">
|
||||
<li><p>Item 1, graf one.</p>
|
||||
<p>Item 1. graf two. The quick brown fox jumped over the lazy dog’s back.</p></li>
|
||||
<p>Item 1. graf two. The quick brown fox jumped over the lazy dog’s
|
||||
back.</p></li>
|
||||
<li><p>Item 2.</p></li>
|
||||
<li><p>Item 3.</p></li>
|
||||
</ol>
|
||||
|
@ -540,18 +545,22 @@ Blah
|
|||
<p>So is <strong><em>this</em></strong> word.</p>
|
||||
<p><strong><em>This is strong and em.</em></strong></p>
|
||||
<p>So is <strong><em>this</em></strong> word.</p>
|
||||
<p>This is code: <code>></code>, <code>$</code>, <code>\</code>, <code>\$</code>, <code><html></code>.</p>
|
||||
<p>This is code: <code>></code>, <code>$</code>, <code>\</code>,
|
||||
<code>\$</code>, <code><html></code>.</p>
|
||||
<p><del>This is <em>strikeout</em>.</del></p>
|
||||
<p>Superscripts: a<sup>bc</sup>d a<sup><em>hello</em></sup> a<sup>hello there</sup>.</p>
|
||||
<p>Superscripts: a<sup>bc</sup>d a<sup><em>hello</em></sup>
|
||||
a<sup>hello there</sup>.</p>
|
||||
<p>Subscripts: H<sub>2</sub>O, H<sub>23</sub>O, H<sub>many of them</sub>O.</p>
|
||||
<p>These should not be superscripts or subscripts, because of the unescaped spaces: a^b c^d, a~b c~d.</p>
|
||||
<p>These should not be superscripts or subscripts, because of the unescaped
|
||||
spaces: a^b c^d, a~b c~d.</p>
|
||||
<hr />
|
||||
<h1 id="smart-quotes-ellipses-dashes">Smart quotes, ellipses, dashes</h1>
|
||||
<p>“Hello,” said the spider. “‘Shelob’ is my name.”</p>
|
||||
<p>‘A’, ‘B’, and ‘C’ are letters.</p>
|
||||
<p>‘Oak,’ ‘elm,’ and ‘beech’ are names of trees. So is ‘pine.’</p>
|
||||
<p>‘He said, “I want to go.”’ Were you alive in the 70’s?</p>
|
||||
<p>Here is some quoted ‘<code>code</code>’ and a “<a href="http://example.com/?foo=1&bar=2">quoted link</a>”.</p>
|
||||
<p>Here is some quoted ‘<code>code</code>’ and a “<a
|
||||
href="http://example.com/?foo=1&bar=2">quoted link</a>”.</p>
|
||||
<p>Some dashes: one—two — three—four — five.</p>
|
||||
<p>Dashes between numbers: 5–7, 255–66, 1987–1999.</p>
|
||||
<p>Ellipses…and…and….</p>
|
||||
|
@ -564,13 +573,16 @@ Blah
|
|||
<li><span class="math inline"><em>α</em> ∧ <em>ω</em></span></li>
|
||||
<li><span class="math inline">223</span></li>
|
||||
<li><span class="math inline"><em>p</em></span>-Tree</li>
|
||||
<li>Here’s some display math: <span class="math display">$$\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}$$</span></li>
|
||||
<li>Here’s one that has a line break in it: <span class="math inline"><em>α</em> + <em>ω</em> × <em>x</em><sup>2</sup></span>.</li>
|
||||
<li>Here’s some display math: <span class="math
|
||||
display">$$\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}$$</span></li>
|
||||
<li>Here’s one that has a line break in it: <span class="math
|
||||
inline"><em>α</em> + <em>ω</em> × <em>x</em><sup>2</sup></span>.</li>
|
||||
</ul>
|
||||
<p>These shouldn’t be math:</p>
|
||||
<ul>
|
||||
<li>To get the famous equation, write <code>$e = mc^2$</code>.</li>
|
||||
<li>$22,000 is a <em>lot</em> of money. So is $34,000. (It worked if “lot” is emphasized.)</li>
|
||||
<li>$22,000 is a <em>lot</em> of money. So is $34,000. (It worked if “lot” is
|
||||
emphasized.)</li>
|
||||
<li>Shoes ($20) and socks ($5).</li>
|
||||
<li>Escaped <code>$</code>: $73 <em>this should be emphasized</em> 23$.</li>
|
||||
</ul>
|
||||
|
@ -613,7 +625,8 @@ Blah
|
|||
<p><a href="/url/" title="title">URL and title</a>.</p>
|
||||
<p><a href="/url/" title="title preceded by two spaces">URL and title</a>.</p>
|
||||
<p><a href="/url/" title="title preceded by a tab">URL and title</a>.</p>
|
||||
<p><a href="/url/" title="title with "quotes" in it">URL and title</a></p>
|
||||
<p><a href="/url/" title="title with "quotes" in it">URL and
|
||||
title</a></p>
|
||||
<p><a href="/url/" title="title with single quotes">URL and title</a></p>
|
||||
<p><a href="/url/with_underscore">with_underscore</a></p>
|
||||
<p><a href="mailto:nobody@nowhere.net">Email link</a></p>
|
||||
|
@ -630,22 +643,29 @@ Blah
|
|||
<p>Foo <a href="/url/" title="Title with "quotes" inside">bar</a>.</p>
|
||||
<p>Foo <a href="/url/" title="Title with "quote" inside">biz</a>.</p>
|
||||
<h2 id="with-ampersands">With ampersands</h2>
|
||||
<p>Here’s a <a href="http://example.com/?foo=1&bar=2">link with an ampersand in the URL</a>.</p>
|
||||
<p>Here’s a link with an amersand in the link text: <a href="http://att.com/" title="AT&T">AT&T</a>.</p>
|
||||
<p>Here’s a <a href="http://example.com/?foo=1&bar=2">link with an ampersand
|
||||
in the URL</a>.</p>
|
||||
<p>Here’s a link with an amersand in the link text: <a href="http://att.com/"
|
||||
title="AT&T">AT&T</a>.</p>
|
||||
<p>Here’s an <a href="/script?foo=1&bar=2">inline link</a>.</p>
|
||||
<p>Here’s an <a href="/script?foo=1&bar=2">inline link in pointy braces</a>.</p>
|
||||
<p>Here’s an <a href="/script?foo=1&bar=2">inline link in pointy
|
||||
braces</a>.</p>
|
||||
<h2 id="autolinks">Autolinks</h2>
|
||||
<p>With an ampersand: <a href="http://example.com/?foo=1&bar=2" class="uri">http://example.com/?foo=1&bar=2</a></p>
|
||||
<p>With an ampersand: <a href="http://example.com/?foo=1&bar=2"
|
||||
class="uri">http://example.com/?foo=1&bar=2</a></p>
|
||||
<ul>
|
||||
<li>In a list?</li>
|
||||
<li><a href="http://example.com/" class="uri">http://example.com/</a></li>
|
||||
<li>It should.</li>
|
||||
</ul>
|
||||
<p>An e-mail address: <a href="mailto:nobody@nowhere.net" class="email">nobody@nowhere.net</a></p>
|
||||
<p>An e-mail address: <a href="mailto:nobody@nowhere.net"
|
||||
class="email">nobody@nowhere.net</a></p>
|
||||
<blockquote>
|
||||
<p>Blockquoted: <a href="http://example.com/" class="uri">http://example.com/</a></p>
|
||||
<p>Blockquoted: <a href="http://example.com/"
|
||||
class="uri">http://example.com/</a></p>
|
||||
</blockquote>
|
||||
<p>Auto-links should not occur here: <code><http://example.com/></code></p>
|
||||
<p>Auto-links should not occur here:
|
||||
<code><http://example.com/></code></p>
|
||||
<pre><code>or here: <http://example.com/></code></pre>
|
||||
<hr />
|
||||
<h1 id="images">Images</h1>
|
||||
|
@ -657,23 +677,36 @@ Blah
|
|||
<p>Here is a movie <img src="movie.jpg" alt="movie" /> icon.</p>
|
||||
<hr />
|
||||
<h1 id="footnotes">Footnotes</h1>
|
||||
<p>Here is a footnote reference,<a href="#fn1" class="footnote-ref" id="fnref1"><sup>1</sup></a> and another.<a href="#fn2" class="footnote-ref" id="fnref2"><sup>2</sup></a> This should <em>not</em> be a footnote reference, because it contains a space.[^my note] Here is an inline note.<a href="#fn3" class="footnote-ref" id="fnref3"><sup>3</sup></a></p>
|
||||
<p>Here is a footnote reference,<a href="#fn1" class="footnote-ref"
|
||||
id="fnref1"><sup>1</sup></a> and another.<a href="#fn2" class="footnote-ref"
|
||||
id="fnref2"><sup>2</sup></a> This should <em>not</em> be a footnote reference,
|
||||
because it contains a space.[^my note] Here is an inline note.<a href="#fn3"
|
||||
class="footnote-ref" id="fnref3"><sup>3</sup></a></p>
|
||||
<blockquote>
|
||||
<p>Notes can go in quotes.<a href="#fn4" class="footnote-ref" id="fnref4"><sup>4</sup></a></p>
|
||||
<p>Notes can go in quotes.<a href="#fn4" class="footnote-ref"
|
||||
id="fnref4"><sup>4</sup></a></p>
|
||||
</blockquote>
|
||||
<ol style="list-style-type: decimal">
|
||||
<li>And in list items.<a href="#fn5" class="footnote-ref" id="fnref5"><sup>5</sup></a></li>
|
||||
<li>And in list items.<a href="#fn5" class="footnote-ref"
|
||||
id="fnref5"><sup>5</sup></a></li>
|
||||
</ol>
|
||||
<p>This paragraph should not be part of the note, as it is not indented.</p>
|
||||
<div class="footnotes footnotes-end-of-document">
|
||||
<hr />
|
||||
<ol>
|
||||
<li id="fn1"><p>Here is the footnote. It can go anywhere after the footnote reference. It need not be placed at the end of the document.<a href="#fnref1" class="footnote-back">↩︎</a></p></li>
|
||||
<li id="fn1"><p>Here is the footnote. It can go anywhere after the footnote
|
||||
reference. It need not be placed at the end of the document.<a href="#fnref1"
|
||||
class="footnote-back">↩︎</a></p></li>
|
||||
<li id="fn2"><p>Here’s the long note. This one contains multiple blocks.</p>
|
||||
<p>Subsequent blocks are indented to show that they belong to the footnote (as with list items).</p>
|
||||
<p>Subsequent blocks are indented to show that they belong to the footnote (as
|
||||
with list items).</p>
|
||||
<pre><code> { <code> }</code></pre>
|
||||
<p>If you want, you can indent every line, but you can also be lazy and just indent the first line of each block.<a href="#fnref2" class="footnote-back">↩︎</a></p></li>
|
||||
<li id="fn3"><p>This is <em>easier</em> to type. Inline notes may contain <a href="http://google.com">links</a> and <code>]</code> verbatim characters, as well as [bracketed text].<a href="#fnref3" class="footnote-back">↩︎</a></p></li>
|
||||
<p>If you want, you can indent every line, but you can also be lazy and just
|
||||
indent the first line of each block.<a href="#fnref2"
|
||||
class="footnote-back">↩︎</a></p></li>
|
||||
<li id="fn3"><p>This is <em>easier</em> to type. Inline notes may contain <a
|
||||
href="http://google.com">links</a> and <code>]</code> verbatim characters, as
|
||||
well as [bracketed text].<a href="#fnref3" class="footnote-back">↩︎</a></p></li>
|
||||
<li id="fn4"><p>In quote.<a href="#fnref4" class="footnote-back">↩︎</a></p></li>
|
||||
<li id="fn5"><p>In list.<a href="#fnref5" class="footnote-back">↩︎</a></p></li>
|
||||
</ol>
|
||||
|
|
|
@ -159,10 +159,12 @@
|
|||
<p class="author">Anonymous</p>
|
||||
<p class="date">July 17, 2006</p>
|
||||
</header>
|
||||
<p>This is a set of tests for pandoc. Most of them are adapted from John Gruber’s markdown test suite.</p>
|
||||
<p>This is a set of tests for pandoc. Most of them are adapted from John
|
||||
Gruber’s markdown test suite.</p>
|
||||
<hr />
|
||||
<h1 id="headers">Headers</h1>
|
||||
<h2 id="level-2-with-an-embedded-link">Level 2 with an <a href="/url">embedded link</a></h2>
|
||||
<h2 id="level-2-with-an-embedded-link">Level 2 with an <a href="/url">embedded
|
||||
link</a></h2>
|
||||
<h3 id="level-3-with-emphasis">Level 3 with <em>emphasis</em></h3>
|
||||
<h4 id="level-4">Level 4</h4>
|
||||
<h5 id="level-5">Level 5</h5>
|
||||
|
@ -175,7 +177,9 @@
|
|||
<hr />
|
||||
<h1 id="paragraphs">Paragraphs</h1>
|
||||
<p>Here’s a regular paragraph.</p>
|
||||
<p>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.</p>
|
||||
<p>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.</p>
|
||||
<p>Here’s one with a bullet. * criminey.</p>
|
||||
<p>There should be a hard line break<br />
|
||||
here.</p>
|
||||
|
@ -286,7 +290,8 @@ These should not be escaped: \$ \\ \> \[ \{</code></pre>
|
|||
<p>Multiple paragraphs:</p>
|
||||
<ol type="1">
|
||||
<li><p>Item 1, graf one.</p>
|
||||
<p>Item 1. graf two. The quick brown fox jumped over the lazy dog’s back.</p></li>
|
||||
<p>Item 1. graf two. The quick brown fox jumped over the lazy dog’s
|
||||
back.</p></li>
|
||||
<li><p>Item 2.</p></li>
|
||||
<li><p>Item 3.</p></li>
|
||||
</ol>
|
||||
|
@ -543,18 +548,22 @@ Blah
|
|||
<p>So is <strong><em>this</em></strong> word.</p>
|
||||
<p><strong><em>This is strong and em.</em></strong></p>
|
||||
<p>So is <strong><em>this</em></strong> word.</p>
|
||||
<p>This is code: <code>></code>, <code>$</code>, <code>\</code>, <code>\$</code>, <code><html></code>.</p>
|
||||
<p>This is code: <code>></code>, <code>$</code>, <code>\</code>,
|
||||
<code>\$</code>, <code><html></code>.</p>
|
||||
<p><del>This is <em>strikeout</em>.</del></p>
|
||||
<p>Superscripts: a<sup>bc</sup>d a<sup><em>hello</em></sup> a<sup>hello there</sup>.</p>
|
||||
<p>Superscripts: a<sup>bc</sup>d a<sup><em>hello</em></sup>
|
||||
a<sup>hello there</sup>.</p>
|
||||
<p>Subscripts: H<sub>2</sub>O, H<sub>23</sub>O, H<sub>many of them</sub>O.</p>
|
||||
<p>These should not be superscripts or subscripts, because of the unescaped spaces: a^b c^d, a~b c~d.</p>
|
||||
<p>These should not be superscripts or subscripts, because of the unescaped
|
||||
spaces: a^b c^d, a~b c~d.</p>
|
||||
<hr />
|
||||
<h1 id="smart-quotes-ellipses-dashes">Smart quotes, ellipses, dashes</h1>
|
||||
<p>“Hello,” said the spider. “‘Shelob’ is my name.”</p>
|
||||
<p>‘A’, ‘B’, and ‘C’ are letters.</p>
|
||||
<p>‘Oak,’ ‘elm,’ and ‘beech’ are names of trees. So is ‘pine.’</p>
|
||||
<p>‘He said, “I want to go.”’ Were you alive in the 70’s?</p>
|
||||
<p>Here is some quoted ‘<code>code</code>’ and a “<a href="http://example.com/?foo=1&bar=2">quoted link</a>”.</p>
|
||||
<p>Here is some quoted ‘<code>code</code>’ and a “<a
|
||||
href="http://example.com/?foo=1&bar=2">quoted link</a>”.</p>
|
||||
<p>Some dashes: one—two — three—four — five.</p>
|
||||
<p>Dashes between numbers: 5–7, 255–66, 1987–1999.</p>
|
||||
<p>Ellipses…and…and….</p>
|
||||
|
@ -567,13 +576,16 @@ Blah
|
|||
<li><span class="math inline"><em>α</em> ∧ <em>ω</em></span></li>
|
||||
<li><span class="math inline">223</span></li>
|
||||
<li><span class="math inline"><em>p</em></span>-Tree</li>
|
||||
<li>Here’s some display math: <span class="math display">$$\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}$$</span></li>
|
||||
<li>Here’s one that has a line break in it: <span class="math inline"><em>α</em> + <em>ω</em> × <em>x</em><sup>2</sup></span>.</li>
|
||||
<li>Here’s some display math: <span class="math
|
||||
display">$$\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}$$</span></li>
|
||||
<li>Here’s one that has a line break in it: <span class="math
|
||||
inline"><em>α</em> + <em>ω</em> × <em>x</em><sup>2</sup></span>.</li>
|
||||
</ul>
|
||||
<p>These shouldn’t be math:</p>
|
||||
<ul>
|
||||
<li>To get the famous equation, write <code>$e = mc^2$</code>.</li>
|
||||
<li>$22,000 is a <em>lot</em> of money. So is $34,000. (It worked if “lot” is emphasized.)</li>
|
||||
<li>$22,000 is a <em>lot</em> of money. So is $34,000. (It worked if “lot” is
|
||||
emphasized.)</li>
|
||||
<li>Shoes ($20) and socks ($5).</li>
|
||||
<li>Escaped <code>$</code>: $73 <em>this should be emphasized</em> 23$.</li>
|
||||
</ul>
|
||||
|
@ -616,7 +628,8 @@ Blah
|
|||
<p><a href="/url/" title="title">URL and title</a>.</p>
|
||||
<p><a href="/url/" title="title preceded by two spaces">URL and title</a>.</p>
|
||||
<p><a href="/url/" title="title preceded by a tab">URL and title</a>.</p>
|
||||
<p><a href="/url/" title="title with "quotes" in it">URL and title</a></p>
|
||||
<p><a href="/url/" title="title with "quotes" in it">URL and
|
||||
title</a></p>
|
||||
<p><a href="/url/" title="title with single quotes">URL and title</a></p>
|
||||
<p><a href="/url/with_underscore">with_underscore</a></p>
|
||||
<p><a href="mailto:nobody@nowhere.net">Email link</a></p>
|
||||
|
@ -633,51 +646,78 @@ Blah
|
|||
<p>Foo <a href="/url/" title="Title with "quotes" inside">bar</a>.</p>
|
||||
<p>Foo <a href="/url/" title="Title with "quote" inside">biz</a>.</p>
|
||||
<h2 id="with-ampersands">With ampersands</h2>
|
||||
<p>Here’s a <a href="http://example.com/?foo=1&bar=2">link with an ampersand in the URL</a>.</p>
|
||||
<p>Here’s a link with an amersand in the link text: <a href="http://att.com/" title="AT&T">AT&T</a>.</p>
|
||||
<p>Here’s a <a href="http://example.com/?foo=1&bar=2">link with an ampersand
|
||||
in the URL</a>.</p>
|
||||
<p>Here’s a link with an amersand in the link text: <a href="http://att.com/"
|
||||
title="AT&T">AT&T</a>.</p>
|
||||
<p>Here’s an <a href="/script?foo=1&bar=2">inline link</a>.</p>
|
||||
<p>Here’s an <a href="/script?foo=1&bar=2">inline link in pointy braces</a>.</p>
|
||||
<p>Here’s an <a href="/script?foo=1&bar=2">inline link in pointy
|
||||
braces</a>.</p>
|
||||
<h2 id="autolinks">Autolinks</h2>
|
||||
<p>With an ampersand: <a href="http://example.com/?foo=1&bar=2" class="uri">http://example.com/?foo=1&bar=2</a></p>
|
||||
<p>With an ampersand: <a href="http://example.com/?foo=1&bar=2"
|
||||
class="uri">http://example.com/?foo=1&bar=2</a></p>
|
||||
<ul>
|
||||
<li>In a list?</li>
|
||||
<li><a href="http://example.com/" class="uri">http://example.com/</a></li>
|
||||
<li>It should.</li>
|
||||
</ul>
|
||||
<p>An e-mail address: <a href="mailto:nobody@nowhere.net" class="email">nobody@nowhere.net</a></p>
|
||||
<p>An e-mail address: <a href="mailto:nobody@nowhere.net"
|
||||
class="email">nobody@nowhere.net</a></p>
|
||||
<blockquote>
|
||||
<p>Blockquoted: <a href="http://example.com/" class="uri">http://example.com/</a></p>
|
||||
<p>Blockquoted: <a href="http://example.com/"
|
||||
class="uri">http://example.com/</a></p>
|
||||
</blockquote>
|
||||
<p>Auto-links should not occur here: <code><http://example.com/></code></p>
|
||||
<p>Auto-links should not occur here:
|
||||
<code><http://example.com/></code></p>
|
||||
<pre><code>or here: <http://example.com/></code></pre>
|
||||
<hr />
|
||||
<h1 id="images">Images</h1>
|
||||
<p>From “Voyage dans la Lune” by Georges Melies (1902):</p>
|
||||
<figure>
|
||||
<img src="lalune.jpg" title="Voyage dans la Lune" alt="lalune" /><figcaption aria-hidden="true">lalune</figcaption>
|
||||
<img src="lalune.jpg" title="Voyage dans la Lune" alt="lalune" />
|
||||
<figcaption aria-hidden="true">lalune</figcaption>
|
||||
</figure>
|
||||
<p>Here is a movie <img src="movie.jpg" alt="movie" /> icon.</p>
|
||||
<hr />
|
||||
<h1 id="footnotes">Footnotes</h1>
|
||||
<p>Here is a footnote reference,<a href="#fn1" class="footnote-ref" id="fnref1" role="doc-noteref"><sup>1</sup></a> and another.<a href="#fn2" class="footnote-ref" id="fnref2" role="doc-noteref"><sup>2</sup></a> This should <em>not</em> be a footnote reference, because it contains a space.[^my note] Here is an inline note.<a href="#fn3" class="footnote-ref" id="fnref3" role="doc-noteref"><sup>3</sup></a></p>
|
||||
<p>Here is a footnote reference,<a href="#fn1" class="footnote-ref" id="fnref1"
|
||||
role="doc-noteref"><sup>1</sup></a> and another.<a href="#fn2"
|
||||
class="footnote-ref" id="fnref2" role="doc-noteref"><sup>2</sup></a> This should
|
||||
<em>not</em> be a footnote reference, because it contains a space.[^my note]
|
||||
Here is an inline note.<a href="#fn3" class="footnote-ref" id="fnref3"
|
||||
role="doc-noteref"><sup>3</sup></a></p>
|
||||
<blockquote>
|
||||
<p>Notes can go in quotes.<a href="#fn4" class="footnote-ref" id="fnref4" role="doc-noteref"><sup>4</sup></a></p>
|
||||
<p>Notes can go in quotes.<a href="#fn4" class="footnote-ref" id="fnref4"
|
||||
role="doc-noteref"><sup>4</sup></a></p>
|
||||
</blockquote>
|
||||
<ol type="1">
|
||||
<li>And in list items.<a href="#fn5" class="footnote-ref" id="fnref5" role="doc-noteref"><sup>5</sup></a></li>
|
||||
<li>And in list items.<a href="#fn5" class="footnote-ref" id="fnref5"
|
||||
role="doc-noteref"><sup>5</sup></a></li>
|
||||
</ol>
|
||||
<p>This paragraph should not be part of the note, as it is not indented.</p>
|
||||
<section class="footnotes footnotes-end-of-document" role="doc-endnotes">
|
||||
<hr />
|
||||
<ol>
|
||||
<li id="fn1" role="doc-endnote"><p>Here is the footnote. It can go anywhere after the footnote reference. It need not be placed at the end of the document.<a href="#fnref1" class="footnote-back" role="doc-backlink">↩︎</a></p></li>
|
||||
<li id="fn2" role="doc-endnote"><p>Here’s the long note. This one contains multiple blocks.</p>
|
||||
<p>Subsequent blocks are indented to show that they belong to the footnote (as with list items).</p>
|
||||
<li id="fn1" role="doc-endnote"><p>Here is the footnote. It can go anywhere
|
||||
after the footnote reference. It need not be placed at the end of the
|
||||
document.<a href="#fnref1" class="footnote-back"
|
||||
role="doc-backlink">↩︎</a></p></li>
|
||||
<li id="fn2" role="doc-endnote"><p>Here’s the long note. This one contains
|
||||
multiple blocks.</p>
|
||||
<p>Subsequent blocks are indented to show that they belong to the footnote (as
|
||||
with list items).</p>
|
||||
<pre><code> { <code> }</code></pre>
|
||||
<p>If you want, you can indent every line, but you can also be lazy and just indent the first line of each block.<a href="#fnref2" class="footnote-back" role="doc-backlink">↩︎</a></p></li>
|
||||
<li id="fn3" role="doc-endnote"><p>This is <em>easier</em> to type. Inline notes may contain <a href="http://google.com">links</a> and <code>]</code> verbatim characters, as well as [bracketed text].<a href="#fnref3" class="footnote-back" role="doc-backlink">↩︎</a></p></li>
|
||||
<li id="fn4" role="doc-endnote"><p>In quote.<a href="#fnref4" class="footnote-back" role="doc-backlink">↩︎</a></p></li>
|
||||
<li id="fn5" role="doc-endnote"><p>In list.<a href="#fnref5" class="footnote-back" role="doc-backlink">↩︎</a></p></li>
|
||||
<p>If you want, you can indent every line, but you can also be lazy and just
|
||||
indent the first line of each block.<a href="#fnref2" class="footnote-back"
|
||||
role="doc-backlink">↩︎</a></p></li>
|
||||
<li id="fn3" role="doc-endnote"><p>This is <em>easier</em> to type. Inline notes
|
||||
may contain <a href="http://google.com">links</a> and <code>]</code> verbatim
|
||||
characters, as well as [bracketed text].<a href="#fnref3" class="footnote-back"
|
||||
role="doc-backlink">↩︎</a></p></li>
|
||||
<li id="fn4" role="doc-endnote"><p>In quote.<a href="#fnref4"
|
||||
class="footnote-back" role="doc-backlink">↩︎</a></p></li>
|
||||
<li id="fn5" role="doc-endnote"><p>In list.<a href="#fnref5"
|
||||
class="footnote-back" role="doc-backlink">↩︎</a></p></li>
|
||||
</ol>
|
||||
</section>
|
||||
</body>
|
||||
|
|
Loading…
Reference in a new issue