Provide explicit separate functions for HTML 4 and 5.
* Text.Pandoc.Writers.HTML: removed writeHtml, writeHtmlString, added writeHtml4, writeHtml4String, writeHtml5, writeHtml5String. * Removed writerHtml5 from WriterOptions. * Renamed default.html template to default.html4. * "html" now aliases to "html5"; to get the old HTML4 behavior, you must now specify "-t html4".
This commit is contained in:
parent
1105dd866c
commit
fce0a60f0a
18 changed files with 883 additions and 96 deletions
|
@ -36,7 +36,7 @@ Description: Pandoc is a Haskell library for converting from one markup
|
|||
only adding a reader or writer.
|
||||
Data-Files:
|
||||
-- templates
|
||||
data/templates/default.html
|
||||
data/templates/default.html4
|
||||
data/templates/default.html5
|
||||
data/templates/default.docbook
|
||||
data/templates/default.docbook5
|
||||
|
@ -150,7 +150,8 @@ Extra-Source-Files:
|
|||
tests/tables.dokuwiki
|
||||
tests/tables.zimwiki
|
||||
tests/tables.icml
|
||||
tests/tables.html
|
||||
tests/tables.html4
|
||||
tests/tables.html5
|
||||
tests/tables.latex
|
||||
tests/tables.man
|
||||
tests/tables.plain
|
||||
|
@ -172,7 +173,8 @@ Extra-Source-Files:
|
|||
tests/writer.context
|
||||
tests/writer.docbook
|
||||
tests/writer.docbook5
|
||||
tests/writer.html
|
||||
tests/writer.html4
|
||||
tests/writer.html5
|
||||
tests/writer.man
|
||||
tests/writer.markdown
|
||||
tests/writer.plain
|
||||
|
|
10
pandoc.hs
10
pandoc.hs
|
@ -111,7 +111,6 @@ convertWithOpts opts args = do
|
|||
, optSectionDivs = sectionDivs
|
||||
, optIncremental = incremental
|
||||
, optSelfContained = selfContained
|
||||
, optHtml5 = html5
|
||||
, optHtmlQTags = htmlQTags
|
||||
, optHighlightStyle = highlightStyle
|
||||
, optTopLevelDivision = topLevelDivision
|
||||
|
@ -188,13 +187,11 @@ convertWithOpts opts args = do
|
|||
(if any isURI sources
|
||||
then "html"
|
||||
else "markdown") sources
|
||||
"html4" -> "html"
|
||||
x -> x
|
||||
|
||||
let writerName' = case map toLower writerName of
|
||||
[] -> defaultWriterName outputFile
|
||||
"epub2" -> "epub"
|
||||
"html4" -> "html"
|
||||
x -> x
|
||||
let format = takeWhile (`notElem` ['+','-'])
|
||||
$ takeFileName writerName' -- in case path to lua script
|
||||
|
@ -203,7 +200,7 @@ convertWithOpts opts args = do
|
|||
|
||||
let laTeXOutput = format `elem` ["latex", "beamer"]
|
||||
let conTeXtOutput = format == "context"
|
||||
let html5Output = format == "html5"
|
||||
let html5Output = format == "html5" || format == "html"
|
||||
|
||||
-- disabling the custom writer for now
|
||||
writer <- if ".lua" `isSuffixOf` format
|
||||
|
@ -313,7 +310,6 @@ convertWithOpts opts args = do
|
|||
writerIdentifierPrefix = idPrefix,
|
||||
writerSourceURL = sourceURL,
|
||||
writerUserDataDir = datadir,
|
||||
writerHtml5 = html5,
|
||||
writerHtmlQTags = htmlQTags,
|
||||
writerTopLevelDivision = topLevelDivision,
|
||||
writerListings = listings,
|
||||
|
@ -413,7 +409,7 @@ convertWithOpts opts args = do
|
|||
err 43 "Error producing PDF"
|
||||
| otherwise -> do
|
||||
let htmlFormat = format `elem`
|
||||
["html","html5","s5","slidy","slideous","dzslides","revealjs"]
|
||||
["html","html4","html5","s5","slidy","slideous","dzslides","revealjs"]
|
||||
selfcontain = if selfContained && htmlFormat
|
||||
then makeSelfContained writerOptions media
|
||||
else return
|
||||
|
@ -523,7 +519,6 @@ data Opt = Opt
|
|||
, optSectionDivs :: Bool -- ^ Put sections in div tags in HTML
|
||||
, optIncremental :: Bool -- ^ Use incremental lists in Slidy/Slideous/S5
|
||||
, optSelfContained :: Bool -- ^ Make HTML accessible offline
|
||||
, optHtml5 :: Bool -- ^ Produce HTML5 in HTML
|
||||
, optHtmlQTags :: Bool -- ^ Use <q> tags in HTML
|
||||
, optHighlightStyle :: Maybe Style -- ^ Style to use for highlighted code
|
||||
, optTopLevelDivision :: TopLevelDivision -- ^ Type of the top-level divisions
|
||||
|
@ -583,7 +578,6 @@ defaultOpts = Opt
|
|||
, optSectionDivs = False
|
||||
, optIncremental = False
|
||||
, optSelfContained = False
|
||||
, optHtml5 = False
|
||||
, optHtmlQTags = False
|
||||
, optHighlightStyle = Just pygments
|
||||
, optTopLevelDivision = TopLevelDefault
|
||||
|
|
|
@ -99,8 +99,10 @@ module Text.Pandoc
|
|||
, writeLaTeX
|
||||
, writeConTeXt
|
||||
, writeTexinfo
|
||||
, writeHtml
|
||||
, writeHtmlString
|
||||
, writeHtml4
|
||||
, writeHtml4String
|
||||
, writeHtml5
|
||||
, writeHtml5String
|
||||
, writeICML
|
||||
, writeDocbook
|
||||
, writeOPML
|
||||
|
@ -281,23 +283,21 @@ writers = [
|
|||
,("epub3" , ByteStringWriter $ \o ->
|
||||
writeEPUB o{ writerEpubVersion = Just EPUB3 })
|
||||
,("fb2" , StringWriter writeFB2)
|
||||
,("html" , StringWriter writeHtmlString)
|
||||
,("html5" , StringWriter $ \o ->
|
||||
writeHtmlString o{ writerHtml5 = True })
|
||||
,("html" , StringWriter writeHtml5String)
|
||||
,("html4" , StringWriter writeHtml4String)
|
||||
,("html5" , StringWriter writeHtml5String)
|
||||
,("icml" , StringWriter writeICML)
|
||||
,("s5" , StringWriter $ \o ->
|
||||
writeHtmlString o{ writerSlideVariant = S5Slides
|
||||
, writerTableOfContents = False })
|
||||
writeHtml4String o{ writerSlideVariant = S5Slides
|
||||
, writerTableOfContents = False })
|
||||
,("slidy" , StringWriter $ \o ->
|
||||
writeHtmlString o{ writerSlideVariant = SlidySlides })
|
||||
writeHtml4String o{ writerSlideVariant = SlidySlides })
|
||||
,("slideous" , StringWriter $ \o ->
|
||||
writeHtmlString o{ writerSlideVariant = SlideousSlides })
|
||||
writeHtml4String o{ writerSlideVariant = SlideousSlides })
|
||||
,("dzslides" , StringWriter $ \o ->
|
||||
writeHtmlString o{ writerSlideVariant = DZSlides
|
||||
, writerHtml5 = True })
|
||||
writeHtml5String o{ writerSlideVariant = DZSlides })
|
||||
,("revealjs" , StringWriter $ \o ->
|
||||
writeHtmlString o{ writerSlideVariant = RevealJsSlides
|
||||
, writerHtml5 = True })
|
||||
writeHtml5String o{ writerSlideVariant = RevealJsSlides })
|
||||
,("docbook" , StringWriter writeDocbook)
|
||||
,("docbook5" , StringWriter $ \o ->
|
||||
writeDocbook o{ writerDocbook5 = True })
|
||||
|
@ -342,6 +342,7 @@ getDefaultExtensions "html" = extensionsFromList
|
|||
[Ext_auto_identifiers,
|
||||
Ext_native_divs,
|
||||
Ext_native_spans]
|
||||
getDefaultExtensions "html4" = getDefaultExtensions "html"
|
||||
getDefaultExtensions "html5" = getDefaultExtensions "html"
|
||||
getDefaultExtensions "epub" = extensionsFromList
|
||||
[Ext_raw_html,
|
||||
|
|
|
@ -168,7 +168,6 @@ data WriterOptions = WriterOptions
|
|||
, writerUserDataDir :: Maybe FilePath -- ^ Path of user data directory
|
||||
, writerCiteMethod :: CiteMethod -- ^ How to print cites
|
||||
, writerDocbook5 :: Bool -- ^ Produce DocBook5
|
||||
, writerHtml5 :: Bool -- ^ Produce HTML5
|
||||
, writerHtmlQTags :: Bool -- ^ Use @<q>@ tags for quotes in HTML
|
||||
, writerBeamer :: Bool -- ^ Produce beamer LaTeX slide show
|
||||
, writerSlideLevel :: Maybe Int -- ^ Force header level of slides
|
||||
|
@ -210,7 +209,6 @@ instance Default WriterOptions where
|
|||
, writerUserDataDir = Nothing
|
||||
, writerCiteMethod = Citeproc
|
||||
, writerDocbook5 = False
|
||||
, writerHtml5 = False
|
||||
, writerHtmlQTags = False
|
||||
, writerBeamer = False
|
||||
, writerSlideLevel = Nothing
|
||||
|
|
|
@ -60,6 +60,7 @@ getDefaultTemplate user writer = do
|
|||
"docx" -> return $ Right ""
|
||||
"fb2" -> return $ Right ""
|
||||
"odt" -> getDefaultTemplate user "opendocument"
|
||||
"html" -> getDefaultTemplate user "html5"
|
||||
"markdown_strict" -> getDefaultTemplate user "markdown"
|
||||
"multimarkdown" -> getDefaultTemplate user "markdown"
|
||||
"markdown_github" -> getDefaultTemplate user "markdown"
|
||||
|
|
|
@ -31,7 +31,7 @@ CommonMark: <http://commonmark.org>
|
|||
-}
|
||||
module Text.Pandoc.Writers.CommonMark (writeCommonMark) where
|
||||
|
||||
import Text.Pandoc.Writers.HTML (writeHtmlString)
|
||||
import Text.Pandoc.Writers.HTML (writeHtml5String)
|
||||
import Text.Pandoc.Definition
|
||||
import Text.Pandoc.Shared (isTightList, linesToPara)
|
||||
import Text.Pandoc.Templates (renderTemplate')
|
||||
|
@ -138,7 +138,7 @@ blockToNodes (DefinitionList items) ns = blockToNodes (BulletList items') ns
|
|||
dlToBullet (term, xs) =
|
||||
Para term : concat xs
|
||||
blockToNodes t@(Table _ _ _ _ _) ns = do
|
||||
s <- writeHtmlString def $! Pandoc nullMeta [t]
|
||||
s <- writeHtml5String def $! Pandoc nullMeta [t]
|
||||
return (node (HTML_BLOCK (T.pack $! s)) [] : ns)
|
||||
blockToNodes Null ns = return ns
|
||||
|
||||
|
|
|
@ -59,7 +59,7 @@ import Control.Monad (mplus, when, zipWithM)
|
|||
import Text.XML.Light ( unode, Element(..), unqual, Attr(..), add_attrs
|
||||
, strContent, lookupAttr, Node(..), QName(..), parseXML
|
||||
, onlyElems, node, ppElement)
|
||||
import Text.Pandoc.Writers.HTML ( writeHtml )
|
||||
import Text.Pandoc.Writers.HTML ( writeHtml4, writeHtml5 )
|
||||
import Data.Char ( toLower, isDigit, isAlphaNum )
|
||||
import Text.Pandoc.MIME (MimeType, getMimeType, extensionFromMimeType)
|
||||
import Text.Blaze.Html.Renderer.Utf8 (renderHtml)
|
||||
|
@ -361,13 +361,15 @@ pandocToEPUB opts doc@(Pandoc meta _) = do
|
|||
: writerVariables opts
|
||||
let opts' = opts{ writerEmailObfuscation = NoObfuscation
|
||||
, writerSectionDivs = True
|
||||
, writerHtml5 = epub3
|
||||
, writerVariables = vars
|
||||
, writerHTMLMathMethod =
|
||||
if epub3
|
||||
then MathML Nothing
|
||||
else writerHTMLMathMethod opts
|
||||
, writerWrapText = WrapAuto }
|
||||
let writeHtml = if epub3
|
||||
then writeHtml5
|
||||
else writeHtml4
|
||||
metadata <- getEPUBMetadata opts' meta
|
||||
|
||||
-- cover page
|
||||
|
@ -376,7 +378,7 @@ pandocToEPUB opts doc@(Pandoc meta _) = do
|
|||
Nothing -> return ([],[])
|
||||
Just img -> do
|
||||
let coverImage = "media/" ++ takeFileName img
|
||||
cpContent <- renderHtml <$> (lift $ writeHtml
|
||||
cpContent <- renderHtml <$> (lift $ writeHtml
|
||||
opts'{ writerVariables = ("coverpage","true"):vars }
|
||||
(Pandoc meta [RawBlock (Format "html") $ "<div id=\"cover-image\">\n<img src=\"" ++ coverImage ++ "\" alt=\"cover image\" />\n</div>"]))
|
||||
imgContent <- lift $ P.readFileLazy img
|
||||
|
@ -484,8 +486,7 @@ pandocToEPUB opts doc@(Pandoc meta _) = do
|
|||
Chapter mbnum $ walk fixInternalReferences bs)
|
||||
chapters'
|
||||
|
||||
let chapToEntry :: PandocMonad m => Int -> Chapter -> m Entry
|
||||
chapToEntry num (Chapter mbnum bs) =
|
||||
let chapToEntry num (Chapter mbnum bs) =
|
||||
(mkEntry (showChapter num) . renderHtml) <$>
|
||||
(writeHtml opts'{ writerNumberOffset =
|
||||
fromMaybe [] mbnum }
|
||||
|
|
|
@ -28,7 +28,9 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
|
|||
|
||||
Conversion of 'Pandoc' documents to HTML.
|
||||
-}
|
||||
module Text.Pandoc.Writers.HTML ( writeHtml , writeHtmlString ) where
|
||||
module Text.Pandoc.Writers.HTML (
|
||||
writeHtml4, writeHtml4String,
|
||||
writeHtml5, writeHtml5String ) where
|
||||
import Text.Pandoc.Definition
|
||||
import Text.Pandoc.Walk
|
||||
import Data.Monoid ((<>))
|
||||
|
@ -80,12 +82,13 @@ data WriterState = WriterState
|
|||
, stHighlighting :: Bool -- ^ Syntax highlighting is used
|
||||
, stSecNum :: [Int] -- ^ Number of current section
|
||||
, stElement :: Bool -- ^ Processing an Element
|
||||
, stHtml5 :: Bool -- ^ Use HTML5
|
||||
}
|
||||
|
||||
defaultWriterState :: WriterState
|
||||
defaultWriterState = WriterState {stNotes= [], stMath = False, stQuotes = False,
|
||||
stHighlighting = False, stSecNum = [],
|
||||
stElement = False}
|
||||
stElement = False, stHtml5 = False}
|
||||
|
||||
-- Helpers to render HTML with the appropriate function.
|
||||
|
||||
|
@ -102,19 +105,35 @@ nl opts = if writerWrapText opts == WrapNone
|
|||
then mempty
|
||||
else preEscapedString "\n"
|
||||
|
||||
-- | Convert Pandoc document to Html string.
|
||||
writeHtmlString :: PandocMonad m => WriterOptions -> Pandoc -> m String
|
||||
writeHtmlString opts d = do
|
||||
(body, context) <- evalStateT (pandocToHtml opts d) defaultWriterState
|
||||
-- | Convert Pandoc document to Html 5 string.
|
||||
writeHtml5String :: PandocMonad m => WriterOptions -> Pandoc -> m String
|
||||
writeHtml5String = writeHtmlString' True
|
||||
|
||||
-- | Convert Pandoc document to Html 5 structure.
|
||||
writeHtml5 :: PandocMonad m => WriterOptions -> Pandoc -> m Html
|
||||
writeHtml5 = writeHtml' True
|
||||
|
||||
-- | Convert Pandoc document to Html 4 string.
|
||||
writeHtml4String :: PandocMonad m => WriterOptions -> Pandoc -> m String
|
||||
writeHtml4String = writeHtmlString' False
|
||||
|
||||
-- | Convert Pandoc document to Html 4 structure.
|
||||
writeHtml4 :: PandocMonad m => WriterOptions -> Pandoc -> m Html
|
||||
writeHtml4 = writeHtml' False
|
||||
|
||||
writeHtmlString' :: PandocMonad m => Bool -> WriterOptions -> Pandoc -> m String
|
||||
writeHtmlString' html5 opts d = do
|
||||
(body, context) <- evalStateT (pandocToHtml opts d)
|
||||
defaultWriterState{ stHtml5 = html5 }
|
||||
return $ case writerTemplate opts of
|
||||
Nothing -> renderHtml body
|
||||
Just tpl -> renderTemplate' tpl $
|
||||
defField "body" (renderHtml body) context
|
||||
|
||||
-- | Convert Pandoc document to Html structure.
|
||||
writeHtml :: PandocMonad m => WriterOptions -> Pandoc -> m Html
|
||||
writeHtml opts d = do
|
||||
(body, context) <- evalStateT (pandocToHtml opts d) defaultWriterState
|
||||
writeHtml' :: PandocMonad m => Bool -> WriterOptions -> Pandoc -> m Html
|
||||
writeHtml' html5 opts d = do
|
||||
(body, context) <- evalStateT (pandocToHtml opts d)
|
||||
defaultWriterState{ stHtml5 = html5 }
|
||||
return $ case writerTemplate opts of
|
||||
Nothing -> body
|
||||
Just tpl -> renderTemplate' tpl $
|
||||
|
@ -144,8 +163,8 @@ pandocToHtml opts (Pandoc meta blocks) = do
|
|||
blocks' <- liftM (mconcat . intersperse (nl opts)) $
|
||||
mapM (elementToHtml slideLevel opts) sects
|
||||
st <- get
|
||||
let notes = reverse (stNotes st)
|
||||
let thebody = blocks' >> footnoteSection opts notes
|
||||
notes <- footnoteSection opts (reverse (stNotes st))
|
||||
let thebody = blocks' >> notes
|
||||
let math = case writerHTMLMathMethod opts of
|
||||
LaTeXMathML (Just url) ->
|
||||
H.script ! A.src (toValue url)
|
||||
|
@ -172,7 +191,7 @@ pandocToHtml opts (Pandoc meta blocks) = do
|
|||
(H.link ! A.rel "stylesheet" ! A.href (toValue css)) <>
|
||||
(H.script ! A.type_ "text/javascript" $ toHtml renderKaTeX)
|
||||
_ -> case lookup "mathml-script" (writerVariables opts) of
|
||||
Just s | not (writerHtml5 opts) ->
|
||||
Just s | not (stHtml5 st) ->
|
||||
H.script ! A.type_ "text/javascript"
|
||||
$ preEscapedString
|
||||
("/*<![CDATA[*/\n" ++ s ++ "/*]]>*/\n")
|
||||
|
@ -199,7 +218,7 @@ pandocToHtml opts (Pandoc meta blocks) = do
|
|||
defField "slideous-url" ("slideous" :: String) $
|
||||
defField "revealjs-url" ("reveal.js" :: String) $
|
||||
defField "s5-url" ("s5/default" :: String) $
|
||||
defField "html5" (writerHtml5 opts) $
|
||||
defField "html5" (stHtml5 st) $
|
||||
metadata
|
||||
return (thebody, context)
|
||||
|
||||
|
@ -277,6 +296,7 @@ elementToHtml slideLevel opts (Sec level num (id',classes,keyvals) title' elemen
|
|||
let slide = writerSlideVariant opts /= NoSlides && level <= slideLevel
|
||||
let num' = zipWith (+) num (writerNumberOffset opts ++ repeat 0)
|
||||
modify $ \st -> st{stSecNum = num'} -- update section number
|
||||
html5 <- gets stHtml5
|
||||
let titleSlide = slide && level < slideLevel
|
||||
header' <- if title' == [Str "\0"] -- marker for hrule
|
||||
then return mempty
|
||||
|
@ -307,10 +327,10 @@ elementToHtml slideLevel opts (Sec level num (id',classes,keyvals) title' elemen
|
|||
let inNl x = mconcat $ nl opts : intersperse (nl opts) x ++ [nl opts]
|
||||
let classes' = ["titleslide" | titleSlide] ++ ["slide" | slide] ++
|
||||
["section" | (slide || writerSectionDivs opts) &&
|
||||
not (writerHtml5 opts) ] ++
|
||||
not html5 ] ++
|
||||
["level" ++ show level | slide || writerSectionDivs opts ]
|
||||
++ classes
|
||||
let secttag = if writerHtml5 opts
|
||||
let secttag = if html5
|
||||
then H5.section
|
||||
else H.div
|
||||
let attr = (id',classes',keyvals)
|
||||
|
@ -327,19 +347,22 @@ elementToHtml slideLevel opts (Sec level num (id',classes,keyvals) title' elemen
|
|||
|
||||
-- | Convert list of Note blocks to a footnote <div>.
|
||||
-- Assumes notes are sorted.
|
||||
footnoteSection :: WriterOptions -> [Html] -> Html
|
||||
footnoteSection opts notes =
|
||||
if null notes
|
||||
then mempty
|
||||
else nl opts >> (container
|
||||
$ nl opts >> hrtag >> nl opts >>
|
||||
H.ol (mconcat notes >> nl opts) >> nl opts)
|
||||
where container x = if writerHtml5 opts
|
||||
then H5.section ! A.class_ "footnotes" $ x
|
||||
else if writerSlideVariant opts /= NoSlides
|
||||
then H.div ! A.class_ "footnotes slide" $ x
|
||||
else H.div ! A.class_ "footnotes" $ x
|
||||
hrtag = if writerHtml5 opts then H5.hr else H.hr
|
||||
footnoteSection :: PandocMonad m
|
||||
=> WriterOptions -> [Html] -> StateT WriterState m Html
|
||||
footnoteSection opts notes = do
|
||||
html5 <- gets stHtml5
|
||||
let hrtag = if html5 then H5.hr else H.hr
|
||||
let container x = if html5
|
||||
then H5.section ! A.class_ "footnotes" $ x
|
||||
else if writerSlideVariant opts /= NoSlides
|
||||
then H.div ! A.class_ "footnotes slide" $ x
|
||||
else H.div ! A.class_ "footnotes" $ x
|
||||
return $
|
||||
if null notes
|
||||
then mempty
|
||||
else nl opts >> (container
|
||||
$ nl opts >> hrtag >> nl opts >>
|
||||
H.ol (mconcat notes >> nl opts) >> nl opts)
|
||||
|
||||
-- | Parse a mailto link; return Just (name, domain) or Nothing.
|
||||
parseMailto :: String -> Maybe (String, String)
|
||||
|
@ -448,13 +471,14 @@ blockToHtml opts (Plain lst) = inlineListToHtml opts lst
|
|||
-- title beginning with fig: indicates that the image is a figure
|
||||
blockToHtml opts (Para [Image attr txt (s,'f':'i':'g':':':tit)]) = do
|
||||
img <- inlineToHtml opts (Image attr txt (s,tit))
|
||||
let tocapt = if writerHtml5 opts
|
||||
html5 <- gets stHtml5
|
||||
let tocapt = if html5
|
||||
then H5.figcaption
|
||||
else H.p ! A.class_ "caption"
|
||||
capt <- if null txt
|
||||
then return mempty
|
||||
else tocapt `fmap` inlineListToHtml opts txt
|
||||
return $ if writerHtml5 opts
|
||||
return $ if html5
|
||||
then H5.figure $ mconcat
|
||||
[nl opts, img, capt, nl opts]
|
||||
else H.div ! A.class_ "figure" $ mconcat
|
||||
|
@ -475,12 +499,13 @@ blockToHtml opts (LineBlock lns) =
|
|||
htmlLines <- mconcat . intersperse lf <$> mapM (inlineListToHtml opts) lns
|
||||
return $ H.div ! A.style "white-space: pre-line;" $ htmlLines
|
||||
blockToHtml opts (Div attr@(ident, classes, kvs) bs) = do
|
||||
html5 <- gets stHtml5
|
||||
let speakerNotes = "notes" `elem` classes
|
||||
-- we don't want incremental output inside speaker notes, see #1394
|
||||
let opts' = if speakerNotes then opts{ writerIncremental = False } else opts
|
||||
contents <- blockListToHtml opts' bs
|
||||
let contents' = nl opts >> contents >> nl opts
|
||||
let (divtag, classes') = if writerHtml5 opts && "section" `elem` classes
|
||||
let (divtag, classes') = if html5 && "section" `elem` classes
|
||||
then (H5.section, filter (/= "section") classes)
|
||||
else (H.div, classes)
|
||||
return $
|
||||
|
@ -498,7 +523,9 @@ blockToHtml opts (RawBlock f str)
|
|||
allowsMathEnvironments (writerHTMLMathMethod opts) &&
|
||||
isMathEnvironment str = blockToHtml opts $ Plain [Math DisplayMath str]
|
||||
| otherwise = return mempty
|
||||
blockToHtml opts (HorizontalRule) = return $ if writerHtml5 opts then H5.hr else H.hr
|
||||
blockToHtml _ (HorizontalRule) = do
|
||||
html5 <- gets stHtml5
|
||||
return $ if html5 then H5.hr else H.hr
|
||||
blockToHtml opts (CodeBlock (id',classes,keyvals) rawCode) = do
|
||||
let tolhs = isEnabled Ext_literate_haskell opts &&
|
||||
any (\c -> map toLower c == "haskell") classes &&
|
||||
|
@ -564,6 +591,7 @@ blockToHtml opts (BulletList lst) = do
|
|||
return $ unordList opts contents
|
||||
blockToHtml opts (OrderedList (startnum, numstyle, _) lst) = do
|
||||
contents <- mapM (blockListToHtml opts) lst
|
||||
html5 <- gets stHtml5
|
||||
let numstyle' = case numstyle of
|
||||
Example -> "decimal"
|
||||
_ -> camelCaseToHyphenated $ show numstyle
|
||||
|
@ -574,7 +602,7 @@ blockToHtml opts (OrderedList (startnum, numstyle, _) lst) = do
|
|||
then [A.class_ "example"]
|
||||
else []) ++
|
||||
(if numstyle /= DefaultStyle
|
||||
then if writerHtml5 opts
|
||||
then if html5
|
||||
then [A.type_ $
|
||||
case numstyle of
|
||||
Decimal -> "1"
|
||||
|
@ -603,6 +631,7 @@ blockToHtml opts (Table capt aligns widths headers rows') = do
|
|||
else do
|
||||
cs <- inlineListToHtml opts capt
|
||||
return $ H.caption cs >> nl opts
|
||||
html5 <- gets stHtml5
|
||||
let percent w = show (truncate (100*w) :: Integer) ++ "%"
|
||||
let coltags = if all (== 0.0) widths
|
||||
then mempty
|
||||
|
@ -610,7 +639,7 @@ blockToHtml opts (Table capt aligns widths headers rows') = do
|
|||
H.colgroup $ do
|
||||
nl opts
|
||||
mapM_ (\w -> do
|
||||
if writerHtml5 opts
|
||||
if html5
|
||||
then H.col ! A.style (toValue $ "width: " ++
|
||||
percent w)
|
||||
else H.col ! A.width (toValue $ percent w)
|
||||
|
@ -666,8 +695,9 @@ tableItemToHtml :: PandocMonad m
|
|||
-> StateT WriterState m Html
|
||||
tableItemToHtml opts tag' align' item = do
|
||||
contents <- blockListToHtml opts item
|
||||
html5 <- gets stHtml5
|
||||
let alignStr = alignmentToString align'
|
||||
let attribs = if writerHtml5 opts
|
||||
let attribs = if html5
|
||||
then A.style (toValue $ "text-align: " ++ alignStr ++ ";")
|
||||
else A.align (toValue alignStr)
|
||||
let tag'' = if null alignStr
|
||||
|
@ -707,7 +737,8 @@ annotateMML e tex = math (unode "semantics" [cs, unode "annotation" (annotAttrs,
|
|||
-- | Convert Pandoc inline element to HTML.
|
||||
inlineToHtml :: PandocMonad m
|
||||
=> WriterOptions -> Inline -> StateT WriterState m Html
|
||||
inlineToHtml opts inline =
|
||||
inlineToHtml opts inline = do
|
||||
html5 <- gets stHtml5
|
||||
case inline of
|
||||
(Str str) -> return $ strToHtml str
|
||||
(Space) -> return $ strToHtml " "
|
||||
|
@ -715,7 +746,7 @@ inlineToHtml opts inline =
|
|||
WrapNone -> preEscapedString " "
|
||||
WrapAuto -> preEscapedString " "
|
||||
WrapPreserve -> preEscapedString "\n"
|
||||
(LineBreak) -> return $ (if writerHtml5 opts then H5.br else H.br)
|
||||
(LineBreak) -> return $ (if html5 then H5.br else H.br)
|
||||
<> strToHtml "\n"
|
||||
(Span (id',classes,kvs) ils)
|
||||
-> inlineListToHtml opts ils >>=
|
||||
|
@ -784,12 +815,12 @@ inlineToHtml opts inline =
|
|||
InlineMath -> H.span ! A.class_ mathClass $ m
|
||||
DisplayMath -> H.div ! A.class_ mathClass $ m
|
||||
WebTeX url -> do
|
||||
let imtag = if writerHtml5 opts then H5.img else H.img
|
||||
let imtag = if html5 then H5.img else H.img
|
||||
let m = imtag ! A.style "vertical-align:middle"
|
||||
! A.src (toValue $ url ++ urlEncode str)
|
||||
! A.alt (toValue str)
|
||||
! A.title (toValue str)
|
||||
let brtag = if writerHtml5 opts then H5.br else H.br
|
||||
let brtag = if html5 then H5.br else H.br
|
||||
return $ case t of
|
||||
InlineMath -> m
|
||||
DisplayMath -> brtag >> m >> brtag
|
||||
|
@ -817,7 +848,7 @@ inlineToHtml opts inline =
|
|||
PlainMath -> do
|
||||
x <- lift (texMathToInlines t str) >>= inlineListToHtml opts
|
||||
let m = H.span ! A.class_ mathClass $ x
|
||||
let brtag = if writerHtml5 opts then H5.br else H.br
|
||||
let brtag = if html5 then H5.br else H.br
|
||||
return $ case t of
|
||||
InlineMath -> m
|
||||
DisplayMath -> brtag >> m >> brtag
|
||||
|
@ -847,7 +878,7 @@ inlineToHtml opts inline =
|
|||
[A.title $ toValue tit | not (null tit)] ++
|
||||
[A.alt $ toValue alternate' | not (null txt)] ++
|
||||
imgAttrsToHtml opts attr
|
||||
let tag = if writerHtml5 opts then H5.img else H.img
|
||||
let tag = if html5 then H5.img else H.img
|
||||
return $ foldl (!) tag attributes
|
||||
-- note: null title included, as in Markdown.pl
|
||||
(Image attr _ (s,tit)) -> do
|
||||
|
@ -880,7 +911,7 @@ inlineToHtml opts inline =
|
|||
(Cite cits il)-> do contents <- inlineListToHtml opts il
|
||||
let citationIds = unwords $ map citationId cits
|
||||
let result = H.span ! A.class_ "citation" $ contents
|
||||
return $ if writerHtml5 opts
|
||||
return $ if html5
|
||||
then result ! customAttribute "data-cites" (toValue citationIds)
|
||||
else result
|
||||
|
||||
|
|
|
@ -47,7 +47,7 @@ import Text.Pandoc.Pretty
|
|||
import Control.Monad.Reader
|
||||
import Control.Monad.State
|
||||
import Control.Monad.Except (throwError)
|
||||
import Text.Pandoc.Writers.HTML (writeHtmlString)
|
||||
import Text.Pandoc.Writers.HTML (writeHtml5String)
|
||||
import Text.Pandoc.Writers.Math (texMathToInlines)
|
||||
import Text.HTML.TagSoup (parseTags, isTagText, Tag(..))
|
||||
import Network.URI (isURI)
|
||||
|
@ -536,7 +536,7 @@ blockToMarkdown' opts t@(Table caption aligns widths headers rows) = do
|
|||
rawHeaders rawRows
|
||||
| isEnabled Ext_raw_html opts -> fmap (id,) $
|
||||
text <$>
|
||||
(writeHtmlString def $ Pandoc nullMeta [t])
|
||||
(writeHtml5String def $ Pandoc nullMeta [t])
|
||||
| otherwise -> return $ (id, text "[TABLE]")
|
||||
return $ nst $ tbl $$ blankline $$ caption'' $$ blankline
|
||||
blockToMarkdown' opts (BulletList items) = do
|
||||
|
@ -1072,7 +1072,7 @@ inlineToMarkdown opts lnk@(Link attr txt (src, tit))
|
|||
| isEnabled Ext_raw_html opts &&
|
||||
not (isEnabled Ext_link_attributes opts) &&
|
||||
attr /= nullAttr = -- use raw HTML
|
||||
(text . trim) <$> writeHtmlString def (Pandoc nullMeta [Plain [lnk]])
|
||||
(text . trim) <$> writeHtml5String def (Pandoc nullMeta [Plain [lnk]])
|
||||
| otherwise = do
|
||||
plain <- asks envPlain
|
||||
linktext <- inlineListToMarkdown opts txt
|
||||
|
@ -1111,7 +1111,7 @@ inlineToMarkdown opts img@(Image attr alternate (source, tit))
|
|||
| isEnabled Ext_raw_html opts &&
|
||||
not (isEnabled Ext_link_attributes opts) &&
|
||||
attr /= nullAttr = -- use raw HTML
|
||||
(text . trim) <$> writeHtmlString def (Pandoc nullMeta [Plain [img]])
|
||||
(text . trim) <$> writeHtml5String def (Pandoc nullMeta [Plain [img]])
|
||||
| otherwise = do
|
||||
plain <- asks envPlain
|
||||
let txt = if null alternate || alternate == [Str source]
|
||||
|
|
|
@ -35,7 +35,7 @@ import Text.Pandoc.Writers.Shared
|
|||
import Text.Pandoc.Shared
|
||||
import Text.Pandoc.Options
|
||||
import Text.Pandoc.Templates (renderTemplate')
|
||||
import Text.Pandoc.Writers.HTML (writeHtmlString)
|
||||
import Text.Pandoc.Writers.HTML (writeHtml5String)
|
||||
import Text.Pandoc.Writers.Markdown (writeMarkdown)
|
||||
import Text.Pandoc.Pretty
|
||||
import Text.Pandoc.Compat.Time
|
||||
|
@ -65,7 +65,7 @@ writeOPML opts (Pandoc meta blocks) = do
|
|||
|
||||
writeHtmlInlines :: PandocMonad m => [Inline] -> m String
|
||||
writeHtmlInlines ils =
|
||||
trim <$> (writeHtmlString def $ Pandoc nullMeta [Plain ils])
|
||||
trim <$> (writeHtml5String def $ Pandoc nullMeta [Plain ils])
|
||||
|
||||
-- date format: RFC 822: Thu, 14 Jul 2005 23:41:05 GMT
|
||||
showDateTimeRFC822 :: UTCTime -> String
|
||||
|
|
|
@ -81,16 +81,17 @@ tests = [ testGroup "markdown"
|
|||
]
|
||||
]
|
||||
, testGroup "html"
|
||||
[ testGroup "writer" (writerTests "html" ++ lhsWriterTests "html")
|
||||
[ testGroup "writer" (writerTests "html4" ++ writerTests "html5" ++
|
||||
lhsWriterTests "html")
|
||||
, test "reader" ["-r", "html", "-w", "native", "-s"]
|
||||
"html-reader.html" "html-reader.native"
|
||||
]
|
||||
, testGroup "s5"
|
||||
[ s5WriterTest "basic" ["-s"] "s5"
|
||||
, s5WriterTest "fancy" ["-s","-m","-i"] "s5"
|
||||
, s5WriterTest "fragment" [] "html"
|
||||
, s5WriterTest "fragment" [] "html4"
|
||||
, s5WriterTest "inserts" ["-s", "-H", "insert",
|
||||
"-B", "insert", "-A", "insert", "-c", "main.css"] "html"
|
||||
"-B", "insert", "-A", "insert", "-c", "main.css"] "html4"
|
||||
]
|
||||
, testGroup "textile"
|
||||
[ testGroup "writer" $ writerTests "textile"
|
||||
|
|
|
@ -8,7 +8,7 @@ import Tests.Helpers
|
|||
import Text.Pandoc.Arbitrary()
|
||||
|
||||
html :: (ToPandoc a) => a -> String
|
||||
html = purely (writeHtmlString def{ writerWrapText = WrapNone }) . toPandoc
|
||||
html = purely (writeHtml4String def{ writerWrapText = WrapNone }) . toPandoc
|
||||
|
||||
{-
|
||||
"my test" =: X =?> Y
|
||||
|
|
|
@ -1,9 +1,9 @@
|
|||
<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd">
|
||||
<html xmlns="http://www.w3.org/1999/xhtml">
|
||||
<!DOCTYPE html>
|
||||
<html>
|
||||
<head>
|
||||
<meta http-equiv="Content-Type" content="text/html; charset=utf-8" />
|
||||
<meta http-equiv="Content-Style-Type" content="text/css" />
|
||||
<meta name="generator" content="pandoc" />
|
||||
<meta charset="utf-8">
|
||||
<meta name="generator" content="pandoc">
|
||||
<meta name="viewport" content="width=device-width, initial-scale=1.0, user-scalable=yes">
|
||||
<title></title>
|
||||
<style type="text/css">code{white-space: pre;}</style>
|
||||
<style type="text/css">
|
||||
|
@ -43,6 +43,9 @@ code > span.an { color: #60a0b0; font-weight: bold; font-style: italic; } /* Ann
|
|||
code > span.cv { color: #60a0b0; font-weight: bold; font-style: italic; } /* CommentVar */
|
||||
code > span.in { color: #60a0b0; font-weight: bold; font-style: italic; } /* Information */
|
||||
</style>
|
||||
<!--[if lt IE 9]>
|
||||
<script src="//cdnjs.cloudflare.com/ajax/libs/html5shiv/3.7.3/html5shiv-printshiv.min.js"></script>
|
||||
<![endif]-->
|
||||
</head>
|
||||
<body>
|
||||
<h1 id="lhs-test">lhs test</h1>
|
||||
|
|
|
@ -1,9 +1,9 @@
|
|||
<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd">
|
||||
<html xmlns="http://www.w3.org/1999/xhtml">
|
||||
<!DOCTYPE html>
|
||||
<html>
|
||||
<head>
|
||||
<meta http-equiv="Content-Type" content="text/html; charset=utf-8" />
|
||||
<meta http-equiv="Content-Style-Type" content="text/css" />
|
||||
<meta name="generator" content="pandoc" />
|
||||
<meta charset="utf-8">
|
||||
<meta name="generator" content="pandoc">
|
||||
<meta name="viewport" content="width=device-width, initial-scale=1.0, user-scalable=yes">
|
||||
<title></title>
|
||||
<style type="text/css">code{white-space: pre;}</style>
|
||||
<style type="text/css">
|
||||
|
@ -43,6 +43,9 @@ code > span.an { color: #60a0b0; font-weight: bold; font-style: italic; } /* Ann
|
|||
code > span.cv { color: #60a0b0; font-weight: bold; font-style: italic; } /* CommentVar */
|
||||
code > span.in { color: #60a0b0; font-weight: bold; font-style: italic; } /* Information */
|
||||
</style>
|
||||
<!--[if lt IE 9]>
|
||||
<script src="//cdnjs.cloudflare.com/ajax/libs/html5shiv/3.7.3/html5shiv-printshiv.min.js"></script>
|
||||
<![endif]-->
|
||||
</head>
|
||||
<body>
|
||||
<h1 id="lhs-test">lhs test</h1>
|
||||
|
|
204
tests/tables.html5
Normal file
204
tests/tables.html5
Normal file
|
@ -0,0 +1,204 @@
|
|||
<p>Simple table with caption:</p>
|
||||
<table>
|
||||
<caption>Demonstration of simple table syntax.</caption>
|
||||
<thead>
|
||||
<tr class="header">
|
||||
<th style="text-align: right;">Right</th>
|
||||
<th style="text-align: left;">Left</th>
|
||||
<th style="text-align: center;">Center</th>
|
||||
<th>Default</th>
|
||||
</tr>
|
||||
</thead>
|
||||
<tbody>
|
||||
<tr class="odd">
|
||||
<td style="text-align: right;">12</td>
|
||||
<td style="text-align: left;">12</td>
|
||||
<td style="text-align: center;">12</td>
|
||||
<td>12</td>
|
||||
</tr>
|
||||
<tr class="even">
|
||||
<td style="text-align: right;">123</td>
|
||||
<td style="text-align: left;">123</td>
|
||||
<td style="text-align: center;">123</td>
|
||||
<td>123</td>
|
||||
</tr>
|
||||
<tr class="odd">
|
||||
<td style="text-align: right;">1</td>
|
||||
<td style="text-align: left;">1</td>
|
||||
<td style="text-align: center;">1</td>
|
||||
<td>1</td>
|
||||
</tr>
|
||||
</tbody>
|
||||
</table>
|
||||
<p>Simple table without caption:</p>
|
||||
<table>
|
||||
<thead>
|
||||
<tr class="header">
|
||||
<th style="text-align: right;">Right</th>
|
||||
<th style="text-align: left;">Left</th>
|
||||
<th style="text-align: center;">Center</th>
|
||||
<th>Default</th>
|
||||
</tr>
|
||||
</thead>
|
||||
<tbody>
|
||||
<tr class="odd">
|
||||
<td style="text-align: right;">12</td>
|
||||
<td style="text-align: left;">12</td>
|
||||
<td style="text-align: center;">12</td>
|
||||
<td>12</td>
|
||||
</tr>
|
||||
<tr class="even">
|
||||
<td style="text-align: right;">123</td>
|
||||
<td style="text-align: left;">123</td>
|
||||
<td style="text-align: center;">123</td>
|
||||
<td>123</td>
|
||||
</tr>
|
||||
<tr class="odd">
|
||||
<td style="text-align: right;">1</td>
|
||||
<td style="text-align: left;">1</td>
|
||||
<td style="text-align: center;">1</td>
|
||||
<td>1</td>
|
||||
</tr>
|
||||
</tbody>
|
||||
</table>
|
||||
<p>Simple table indented two spaces:</p>
|
||||
<table>
|
||||
<caption>Demonstration of simple table syntax.</caption>
|
||||
<thead>
|
||||
<tr class="header">
|
||||
<th style="text-align: right;">Right</th>
|
||||
<th style="text-align: left;">Left</th>
|
||||
<th style="text-align: center;">Center</th>
|
||||
<th>Default</th>
|
||||
</tr>
|
||||
</thead>
|
||||
<tbody>
|
||||
<tr class="odd">
|
||||
<td style="text-align: right;">12</td>
|
||||
<td style="text-align: left;">12</td>
|
||||
<td style="text-align: center;">12</td>
|
||||
<td>12</td>
|
||||
</tr>
|
||||
<tr class="even">
|
||||
<td style="text-align: right;">123</td>
|
||||
<td style="text-align: left;">123</td>
|
||||
<td style="text-align: center;">123</td>
|
||||
<td>123</td>
|
||||
</tr>
|
||||
<tr class="odd">
|
||||
<td style="text-align: right;">1</td>
|
||||
<td style="text-align: left;">1</td>
|
||||
<td style="text-align: center;">1</td>
|
||||
<td>1</td>
|
||||
</tr>
|
||||
</tbody>
|
||||
</table>
|
||||
<p>Multiline table with caption:</p>
|
||||
<table style="width:79%;">
|
||||
<caption>Here’s the caption. It may span multiple lines.</caption>
|
||||
<colgroup>
|
||||
<col style="width: 15%" />
|
||||
<col style="width: 13%" />
|
||||
<col style="width: 16%" />
|
||||
<col style="width: 33%" />
|
||||
</colgroup>
|
||||
<thead>
|
||||
<tr class="header">
|
||||
<th style="text-align: center;">Centered Header</th>
|
||||
<th style="text-align: left;">Left Aligned</th>
|
||||
<th style="text-align: right;">Right Aligned</th>
|
||||
<th style="text-align: left;">Default aligned</th>
|
||||
</tr>
|
||||
</thead>
|
||||
<tbody>
|
||||
<tr class="odd">
|
||||
<td style="text-align: center;">First</td>
|
||||
<td style="text-align: left;">row</td>
|
||||
<td style="text-align: right;">12.0</td>
|
||||
<td style="text-align: left;">Example of a row that spans multiple lines.</td>
|
||||
</tr>
|
||||
<tr class="even">
|
||||
<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>
|
||||
</tr>
|
||||
</tbody>
|
||||
</table>
|
||||
<p>Multiline table without caption:</p>
|
||||
<table style="width:79%;">
|
||||
<colgroup>
|
||||
<col style="width: 15%" />
|
||||
<col style="width: 13%" />
|
||||
<col style="width: 16%" />
|
||||
<col style="width: 33%" />
|
||||
</colgroup>
|
||||
<thead>
|
||||
<tr class="header">
|
||||
<th style="text-align: center;">Centered Header</th>
|
||||
<th style="text-align: left;">Left Aligned</th>
|
||||
<th style="text-align: right;">Right Aligned</th>
|
||||
<th style="text-align: left;">Default aligned</th>
|
||||
</tr>
|
||||
</thead>
|
||||
<tbody>
|
||||
<tr class="odd">
|
||||
<td style="text-align: center;">First</td>
|
||||
<td style="text-align: left;">row</td>
|
||||
<td style="text-align: right;">12.0</td>
|
||||
<td style="text-align: left;">Example of a row that spans multiple lines.</td>
|
||||
</tr>
|
||||
<tr class="even">
|
||||
<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>
|
||||
</tr>
|
||||
</tbody>
|
||||
</table>
|
||||
<p>Table without column headers:</p>
|
||||
<table>
|
||||
<tbody>
|
||||
<tr class="odd">
|
||||
<td style="text-align: right;">12</td>
|
||||
<td style="text-align: left;">12</td>
|
||||
<td style="text-align: center;">12</td>
|
||||
<td style="text-align: right;">12</td>
|
||||
</tr>
|
||||
<tr class="even">
|
||||
<td style="text-align: right;">123</td>
|
||||
<td style="text-align: left;">123</td>
|
||||
<td style="text-align: center;">123</td>
|
||||
<td style="text-align: right;">123</td>
|
||||
</tr>
|
||||
<tr class="odd">
|
||||
<td style="text-align: right;">1</td>
|
||||
<td style="text-align: left;">1</td>
|
||||
<td style="text-align: center;">1</td>
|
||||
<td style="text-align: right;">1</td>
|
||||
</tr>
|
||||
</tbody>
|
||||
</table>
|
||||
<p>Multiline table without column headers:</p>
|
||||
<table style="width:79%;">
|
||||
<colgroup>
|
||||
<col style="width: 15%" />
|
||||
<col style="width: 13%" />
|
||||
<col style="width: 16%" />
|
||||
<col style="width: 33%" />
|
||||
</colgroup>
|
||||
<tbody>
|
||||
<tr class="odd">
|
||||
<td style="text-align: center;">First</td>
|
||||
<td style="text-align: left;">row</td>
|
||||
<td style="text-align: right;">12.0</td>
|
||||
<td>Example of a row that spans multiple lines.</td>
|
||||
</tr>
|
||||
<tr class="even">
|
||||
<td style="text-align: center;">Second</td>
|
||||
<td style="text-align: left;">row</td>
|
||||
<td style="text-align: right;">5.0</td>
|
||||
<td>Here’s another one. Note the blank line between rows.</td>
|
||||
</tr>
|
||||
</tbody>
|
||||
</table>
|
548
tests/writer.html5
Normal file
548
tests/writer.html5
Normal file
|
@ -0,0 +1,548 @@
|
|||
<!DOCTYPE html>
|
||||
<html>
|
||||
<head>
|
||||
<meta charset="utf-8">
|
||||
<meta name="generator" content="pandoc">
|
||||
<meta name="viewport" content="width=device-width, initial-scale=1.0, user-scalable=yes">
|
||||
<meta name="author" content="John MacFarlane">
|
||||
<meta name="author" content="Anonymous">
|
||||
<meta name="dcterms.date" content="2006-07-17">
|
||||
<title>Pandoc Test Suite</title>
|
||||
<style type="text/css">code{white-space: pre;}</style>
|
||||
<!--[if lt IE 9]>
|
||||
<script src="//cdnjs.cloudflare.com/ajax/libs/html5shiv/3.7.3/html5shiv-printshiv.min.js"></script>
|
||||
<![endif]-->
|
||||
</head>
|
||||
<body>
|
||||
<header>
|
||||
<h1 class="title">Pandoc Test Suite</h1>
|
||||
<p class="author">John MacFarlane</p>
|
||||
<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>
|
||||
<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>
|
||||
<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>
|
||||
<h1 id="level-1">Level 1</h1>
|
||||
<h2 id="level-2-with-emphasis">Level 2 with <em>emphasis</em></h2>
|
||||
<h3 id="level-3">Level 3</h3>
|
||||
<p>with no blank line</p>
|
||||
<h2 id="level-2">Level 2</h2>
|
||||
<p>with no blank line</p>
|
||||
<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>Here’s one with a bullet. * criminey.</p>
|
||||
<p>There should be a hard line break<br />
|
||||
here.</p>
|
||||
<hr />
|
||||
<h1 id="block-quotes">Block Quotes</h1>
|
||||
<p>E-mail style:</p>
|
||||
<blockquote>
|
||||
<p>This is a block quote. It is pretty short.</p>
|
||||
</blockquote>
|
||||
<blockquote>
|
||||
<p>Code in a block quote:</p>
|
||||
<pre><code>sub status {
|
||||
print "working";
|
||||
}</code></pre>
|
||||
<p>A list:</p>
|
||||
<ol type="1">
|
||||
<li>item one</li>
|
||||
<li>item two</li>
|
||||
</ol>
|
||||
<p>Nested block quotes:</p>
|
||||
<blockquote>
|
||||
<p>nested</p>
|
||||
</blockquote>
|
||||
<blockquote>
|
||||
<p>nested</p>
|
||||
</blockquote>
|
||||
</blockquote>
|
||||
<p>This should not be a block quote: 2 > 1.</p>
|
||||
<p>And a following paragraph.</p>
|
||||
<hr />
|
||||
<h1 id="code-blocks">Code Blocks</h1>
|
||||
<p>Code:</p>
|
||||
<pre><code>---- (should be four hyphens)
|
||||
|
||||
sub status {
|
||||
print "working";
|
||||
}
|
||||
|
||||
this code block is indented by one tab</code></pre>
|
||||
<p>And:</p>
|
||||
<pre><code> this code block is indented by two tabs
|
||||
|
||||
These should not be escaped: \$ \\ \> \[ \{</code></pre>
|
||||
<hr />
|
||||
<h1 id="lists">Lists</h1>
|
||||
<h2 id="unordered">Unordered</h2>
|
||||
<p>Asterisks tight:</p>
|
||||
<ul>
|
||||
<li>asterisk 1</li>
|
||||
<li>asterisk 2</li>
|
||||
<li>asterisk 3</li>
|
||||
</ul>
|
||||
<p>Asterisks loose:</p>
|
||||
<ul>
|
||||
<li><p>asterisk 1</p></li>
|
||||
<li><p>asterisk 2</p></li>
|
||||
<li><p>asterisk 3</p></li>
|
||||
</ul>
|
||||
<p>Pluses tight:</p>
|
||||
<ul>
|
||||
<li>Plus 1</li>
|
||||
<li>Plus 2</li>
|
||||
<li>Plus 3</li>
|
||||
</ul>
|
||||
<p>Pluses loose:</p>
|
||||
<ul>
|
||||
<li><p>Plus 1</p></li>
|
||||
<li><p>Plus 2</p></li>
|
||||
<li><p>Plus 3</p></li>
|
||||
</ul>
|
||||
<p>Minuses tight:</p>
|
||||
<ul>
|
||||
<li>Minus 1</li>
|
||||
<li>Minus 2</li>
|
||||
<li>Minus 3</li>
|
||||
</ul>
|
||||
<p>Minuses loose:</p>
|
||||
<ul>
|
||||
<li><p>Minus 1</p></li>
|
||||
<li><p>Minus 2</p></li>
|
||||
<li><p>Minus 3</p></li>
|
||||
</ul>
|
||||
<h2 id="ordered">Ordered</h2>
|
||||
<p>Tight:</p>
|
||||
<ol type="1">
|
||||
<li>First</li>
|
||||
<li>Second</li>
|
||||
<li>Third</li>
|
||||
</ol>
|
||||
<p>and:</p>
|
||||
<ol type="1">
|
||||
<li>One</li>
|
||||
<li>Two</li>
|
||||
<li>Three</li>
|
||||
</ol>
|
||||
<p>Loose using tabs:</p>
|
||||
<ol type="1">
|
||||
<li><p>First</p></li>
|
||||
<li><p>Second</p></li>
|
||||
<li><p>Third</p></li>
|
||||
</ol>
|
||||
<p>and using spaces:</p>
|
||||
<ol type="1">
|
||||
<li><p>One</p></li>
|
||||
<li><p>Two</p></li>
|
||||
<li><p>Three</p></li>
|
||||
</ol>
|
||||
<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>
|
||||
<li><p>Item 2.</p></li>
|
||||
<li><p>Item 3.</p></li>
|
||||
</ol>
|
||||
<h2 id="nested">Nested</h2>
|
||||
<ul>
|
||||
<li>Tab
|
||||
<ul>
|
||||
<li>Tab
|
||||
<ul>
|
||||
<li>Tab</li>
|
||||
</ul></li>
|
||||
</ul></li>
|
||||
</ul>
|
||||
<p>Here’s another:</p>
|
||||
<ol type="1">
|
||||
<li>First</li>
|
||||
<li>Second:
|
||||
<ul>
|
||||
<li>Fee</li>
|
||||
<li>Fie</li>
|
||||
<li>Foe</li>
|
||||
</ul></li>
|
||||
<li>Third</li>
|
||||
</ol>
|
||||
<p>Same thing but with paragraphs:</p>
|
||||
<ol type="1">
|
||||
<li><p>First</p></li>
|
||||
<li><p>Second:</p>
|
||||
<ul>
|
||||
<li>Fee</li>
|
||||
<li>Fie</li>
|
||||
<li>Foe</li>
|
||||
</ul></li>
|
||||
<li><p>Third</p></li>
|
||||
</ol>
|
||||
<h2 id="tabs-and-spaces">Tabs and spaces</h2>
|
||||
<ul>
|
||||
<li><p>this is a list item indented with tabs</p></li>
|
||||
<li><p>this is a list item indented with spaces</p>
|
||||
<ul>
|
||||
<li><p>this is an example list item indented with tabs</p></li>
|
||||
<li><p>this is an example list item indented with spaces</p></li>
|
||||
</ul></li>
|
||||
</ul>
|
||||
<h2 id="fancy-list-markers">Fancy list markers</h2>
|
||||
<ol start="2" type="1">
|
||||
<li>begins with 2</li>
|
||||
<li><p>and now 3</p>
|
||||
<p>with a continuation</p>
|
||||
<ol start="4" type="i">
|
||||
<li>sublist with roman numerals, starting with 4</li>
|
||||
<li>more items
|
||||
<ol type="A">
|
||||
<li>a subsublist</li>
|
||||
<li>a subsublist</li>
|
||||
</ol></li>
|
||||
</ol></li>
|
||||
</ol>
|
||||
<p>Nesting:</p>
|
||||
<ol type="A">
|
||||
<li>Upper Alpha
|
||||
<ol type="I">
|
||||
<li>Upper Roman.
|
||||
<ol start="6" type="1">
|
||||
<li>Decimal start with 6
|
||||
<ol start="3" type="a">
|
||||
<li>Lower alpha with paren</li>
|
||||
</ol></li>
|
||||
</ol></li>
|
||||
</ol></li>
|
||||
</ol>
|
||||
<p>Autonumbering:</p>
|
||||
<ol>
|
||||
<li>Autonumber.</li>
|
||||
<li>More.
|
||||
<ol>
|
||||
<li>Nested.</li>
|
||||
</ol></li>
|
||||
</ol>
|
||||
<p>Should not be a list item:</p>
|
||||
<p>M.A. 2007</p>
|
||||
<p>B. Williams</p>
|
||||
<hr />
|
||||
<h1 id="definition-lists">Definition Lists</h1>
|
||||
<p>Tight using spaces:</p>
|
||||
<dl>
|
||||
<dt>apple</dt>
|
||||
<dd>red fruit
|
||||
</dd>
|
||||
<dt>orange</dt>
|
||||
<dd>orange fruit
|
||||
</dd>
|
||||
<dt>banana</dt>
|
||||
<dd>yellow fruit
|
||||
</dd>
|
||||
</dl>
|
||||
<p>Tight using tabs:</p>
|
||||
<dl>
|
||||
<dt>apple</dt>
|
||||
<dd>red fruit
|
||||
</dd>
|
||||
<dt>orange</dt>
|
||||
<dd>orange fruit
|
||||
</dd>
|
||||
<dt>banana</dt>
|
||||
<dd>yellow fruit
|
||||
</dd>
|
||||
</dl>
|
||||
<p>Loose:</p>
|
||||
<dl>
|
||||
<dt>apple</dt>
|
||||
<dd><p>red fruit</p>
|
||||
</dd>
|
||||
<dt>orange</dt>
|
||||
<dd><p>orange fruit</p>
|
||||
</dd>
|
||||
<dt>banana</dt>
|
||||
<dd><p>yellow fruit</p>
|
||||
</dd>
|
||||
</dl>
|
||||
<p>Multiple blocks with italics:</p>
|
||||
<dl>
|
||||
<dt><em>apple</em></dt>
|
||||
<dd><p>red fruit</p>
|
||||
<p>contains seeds, crisp, pleasant to taste</p>
|
||||
</dd>
|
||||
<dt><em>orange</em></dt>
|
||||
<dd><p>orange fruit</p>
|
||||
<pre><code>{ orange code block }</code></pre>
|
||||
<blockquote>
|
||||
<p>orange block quote</p>
|
||||
</blockquote>
|
||||
</dd>
|
||||
</dl>
|
||||
<p>Multiple definitions, tight:</p>
|
||||
<dl>
|
||||
<dt>apple</dt>
|
||||
<dd>red fruit
|
||||
</dd>
|
||||
<dd>computer
|
||||
</dd>
|
||||
<dt>orange</dt>
|
||||
<dd>orange fruit
|
||||
</dd>
|
||||
<dd>bank
|
||||
</dd>
|
||||
</dl>
|
||||
<p>Multiple definitions, loose:</p>
|
||||
<dl>
|
||||
<dt>apple</dt>
|
||||
<dd><p>red fruit</p>
|
||||
</dd>
|
||||
<dd><p>computer</p>
|
||||
</dd>
|
||||
<dt>orange</dt>
|
||||
<dd><p>orange fruit</p>
|
||||
</dd>
|
||||
<dd><p>bank</p>
|
||||
</dd>
|
||||
</dl>
|
||||
<p>Blank line after term, indented marker, alternate markers:</p>
|
||||
<dl>
|
||||
<dt>apple</dt>
|
||||
<dd><p>red fruit</p>
|
||||
</dd>
|
||||
<dd><p>computer</p>
|
||||
</dd>
|
||||
<dt>orange</dt>
|
||||
<dd><p>orange fruit</p>
|
||||
<ol type="1">
|
||||
<li>sublist</li>
|
||||
<li>sublist</li>
|
||||
</ol>
|
||||
</dd>
|
||||
</dl>
|
||||
<h1 id="html-blocks">HTML Blocks</h1>
|
||||
<p>Simple block on one line:</p>
|
||||
<div>
|
||||
foo
|
||||
</div>
|
||||
<p>And nested without indentation:</p>
|
||||
<div>
|
||||
<div>
|
||||
<div>
|
||||
<p>foo</p>
|
||||
</div>
|
||||
</div>
|
||||
<div>
|
||||
bar
|
||||
</div>
|
||||
</div>
|
||||
<p>Interpreted markdown in a table:</p>
|
||||
<table>
|
||||
<tr>
|
||||
<td>
|
||||
This is <em>emphasized</em>
|
||||
</td>
|
||||
<td>
|
||||
And this is <strong>strong</strong>
|
||||
</td>
|
||||
</tr>
|
||||
</table>
|
||||
<script type="text/javascript">document.write('This *should not* be interpreted as markdown');</script>
|
||||
<p>Here’s a simple block:</p>
|
||||
<div>
|
||||
<p>foo</p>
|
||||
</div>
|
||||
<p>This should be a code block, though:</p>
|
||||
<pre><code><div>
|
||||
foo
|
||||
</div></code></pre>
|
||||
<p>As should this:</p>
|
||||
<pre><code><div>foo</div></code></pre>
|
||||
<p>Now, nested:</p>
|
||||
<div>
|
||||
<div>
|
||||
<div>
|
||||
foo
|
||||
</div>
|
||||
</div>
|
||||
</div>
|
||||
<p>This should just be an HTML comment:</p>
|
||||
<!-- Comment -->
|
||||
<p>Multiline:</p>
|
||||
<!--
|
||||
Blah
|
||||
Blah
|
||||
-->
|
||||
<!--
|
||||
This is another comment.
|
||||
-->
|
||||
<p>Code block:</p>
|
||||
<pre><code><!-- Comment --></code></pre>
|
||||
<p>Just plain comment, with trailing spaces on the line:</p>
|
||||
<!-- foo -->
|
||||
<p>Code:</p>
|
||||
<pre><code><hr /></code></pre>
|
||||
<p>Hr’s:</p>
|
||||
<hr>
|
||||
<hr />
|
||||
<hr />
|
||||
<hr>
|
||||
<hr />
|
||||
<hr />
|
||||
<hr class="foo" id="bar" />
|
||||
<hr class="foo" id="bar" />
|
||||
<hr class="foo" id="bar">
|
||||
<hr />
|
||||
<h1 id="inline-markup">Inline Markup</h1>
|
||||
<p>This is <em>emphasized</em>, and so <em>is this</em>.</p>
|
||||
<p>This is <strong>strong</strong>, and so <strong>is this</strong>.</p>
|
||||
<p>An <em><a href="/url">emphasized link</a></em>.</p>
|
||||
<p><strong><em>This is strong and em.</em></strong></p>
|
||||
<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><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>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>
|
||||
<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>Some dashes: one—two — three—four — five.</p>
|
||||
<p>Dashes between numbers: 5–7, 255–66, 1987–1999.</p>
|
||||
<p>Ellipses…and…and….</p>
|
||||
<hr />
|
||||
<h1 id="latex">LaTeX</h1>
|
||||
<ul>
|
||||
<li></li>
|
||||
<li><span class="math inline">2 + 2 = 4</span></li>
|
||||
<li><span class="math inline"><em>x</em> ∈ <em>y</em></span></li>
|
||||
<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: <br /><span class="math display">$$\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}$$</span><br /></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>Shoes ($20) and socks ($5).</li>
|
||||
<li>Escaped <code>$</code>: $73 <em>this should be emphasized</em> 23$.</li>
|
||||
</ul>
|
||||
<p>Here’s a LaTeX table:</p>
|
||||
|
||||
<hr />
|
||||
<h1 id="special-characters">Special Characters</h1>
|
||||
<p>Here is some unicode:</p>
|
||||
<ul>
|
||||
<li>I hat: Î</li>
|
||||
<li>o umlaut: ö</li>
|
||||
<li>section: §</li>
|
||||
<li>set membership: ∈</li>
|
||||
<li>copyright: ©</li>
|
||||
</ul>
|
||||
<p>AT&T has an ampersand in their name.</p>
|
||||
<p>AT&T is another way to write it.</p>
|
||||
<p>This & that.</p>
|
||||
<p>4 < 5.</p>
|
||||
<p>6 > 5.</p>
|
||||
<p>Backslash: \</p>
|
||||
<p>Backtick: `</p>
|
||||
<p>Asterisk: *</p>
|
||||
<p>Underscore: _</p>
|
||||
<p>Left brace: {</p>
|
||||
<p>Right brace: }</p>
|
||||
<p>Left bracket: [</p>
|
||||
<p>Right bracket: ]</p>
|
||||
<p>Left paren: (</p>
|
||||
<p>Right paren: )</p>
|
||||
<p>Greater-than: ></p>
|
||||
<p>Hash: #</p>
|
||||
<p>Period: .</p>
|
||||
<p>Bang: !</p>
|
||||
<p>Plus: +</p>
|
||||
<p>Minus: -</p>
|
||||
<hr />
|
||||
<h1 id="links">Links</h1>
|
||||
<h2 id="explicit">Explicit</h2>
|
||||
<p>Just a <a href="/url/">URL</a>.</p>
|
||||
<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 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>
|
||||
<p><a href="">Empty</a>.</p>
|
||||
<h2 id="reference">Reference</h2>
|
||||
<p>Foo <a href="/url/">bar</a>.</p>
|
||||
<p>Foo <a href="/url/">bar</a>.</p>
|
||||
<p>Foo <a href="/url/">bar</a>.</p>
|
||||
<p>With <a href="/url/">embedded [brackets]</a>.</p>
|
||||
<p><a href="/url/">b</a> by itself should be a link.</p>
|
||||
<p>Indented <a href="/url">once</a>.</p>
|
||||
<p>Indented <a href="/url">twice</a>.</p>
|
||||
<p>Indented <a href="/url">thrice</a>.</p>
|
||||
<p>This should [not][] be a link.</p>
|
||||
<pre><code>[not]: /url</code></pre>
|
||||
<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 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>
|
||||
<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>
|
||||
<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">nobody@nowhere.net</a></p>
|
||||
<blockquote>
|
||||
<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>
|
||||
<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>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="footnoteRef" id="fnref1"><sup>1</sup></a> and another.<a href="#fn2" class="footnoteRef" 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="footnoteRef" id="fnref3"><sup>3</sup></a></p>
|
||||
<blockquote>
|
||||
<p>Notes can go in quotes.<a href="#fn4" class="footnoteRef" id="fnref4"><sup>4</sup></a></p>
|
||||
</blockquote>
|
||||
<ol type="1">
|
||||
<li>And in list items.<a href="#fn5" class="footnoteRef" id="fnref5"><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">
|
||||
<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">↩</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>
|
||||
<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">↩</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">↩</a></p></li>
|
||||
<li id="fn4"><p>In quote.<a href="#fnref4">↩</a></p></li>
|
||||
<li id="fn5"><p>In list.<a href="#fnref5">↩</a></p></li>
|
||||
</ol>
|
||||
</section>
|
||||
</body>
|
||||
</html>
|
Loading…
Add table
Reference in a new issue