Merge branch 'master' into tests
This commit is contained in:
commit
5da2d1e66c
13 changed files with 130 additions and 55 deletions
16
README
16
README
|
@ -208,6 +208,10 @@ Options
|
|||
`markdown` or `textile`. It is selected automatically when the input
|
||||
format is `textile` or the output format is `latex` or `context`.)
|
||||
|
||||
`-5`, `--html5`
|
||||
: Produce HTML5 instead of HTML4. This option has no effect for writers
|
||||
other than `html`.
|
||||
|
||||
`-m` *URL*, `--latexmathml=`*URL*
|
||||
: Use the [LaTeXMathML] script to display embedded TeX math in HTML output.
|
||||
To insert a link to a local copy of the `LaTeXMathML.js` script,
|
||||
|
@ -262,8 +266,9 @@ Options
|
|||
By default, sections are not numbered.
|
||||
|
||||
`--section-divs`
|
||||
: Wrap sections in `<div>` tags, and attach identifiers to the
|
||||
enclosing `<div>` rather than the header itself.
|
||||
: Wrap sections in `<div>` tags (or `<section>` tags in HTML5),
|
||||
and attach identifiers to the enclosing `<div>` (or `<section>`)
|
||||
rather than the header itself.
|
||||
See [Section identifiers](#header-identifiers-in-html), below.
|
||||
|
||||
`--no-wrap`
|
||||
|
@ -504,6 +509,8 @@ depending on the output format, but include:
|
|||
multiple values)
|
||||
`date`
|
||||
: date of document, as specified in title block
|
||||
`lang`
|
||||
: language code for HTML documents
|
||||
|
||||
Variables may be set at the command line using the `-V/--variable`
|
||||
option. This allows users to include custom variables in their
|
||||
|
@ -1143,8 +1150,9 @@ Note, however, that this method of providing links to sections works
|
|||
only in HTML.
|
||||
|
||||
If the `--section-divs` option is specified, then each section will
|
||||
be wrapped in a `div`, and the identifier will be attached to the
|
||||
enclosing `<div>` tag rather than the header itself. This allows entire
|
||||
be wrapped in a `div` (or a `section`, if `--html5` was specified),
|
||||
and the identifier will be attached to the enclosing `<div>`
|
||||
(or `<section>`) tag rather than the header itself. This allows entire
|
||||
sections to be manipulated using javascript or treated differently in
|
||||
CSS.
|
||||
|
||||
|
|
6
Setup.hs
6
Setup.hs
|
@ -9,7 +9,7 @@ import Distribution.Verbosity ( Verbosity, silent )
|
|||
import Distribution.Simple.InstallDirs (mandir, bindir, CopyDest (NoCopyDest))
|
||||
import Distribution.Simple.Utils (copyFiles)
|
||||
import Control.Exception ( bracket_ )
|
||||
import Control.Monad ( unless, when )
|
||||
import Control.Monad ( unless )
|
||||
import System.Process ( rawSystem, runCommand, runProcess, waitForProcess )
|
||||
import System.FilePath ( (</>), (<.>) )
|
||||
import System.Directory
|
||||
|
@ -50,8 +50,8 @@ runTestSuite args _ pkg lbi = do
|
|||
|
||||
-- | Build man pages from markdown sources in man/man1/.
|
||||
makeManPages :: Args -> BuildFlags -> PackageDescription -> LocalBuildInfo -> IO ()
|
||||
makeManPages _ flags _ buildInfo = do
|
||||
let pandocPath = (buildDir buildInfo) </> "pandoc" </> "pandoc"
|
||||
makeManPages _ flags _ bi = do
|
||||
let pandocPath = (buildDir bi) </> "pandoc" </> "pandoc"
|
||||
makeManPage pandocPath (fromFlag $ buildVerbosity flags) "markdown2pdf.1"
|
||||
let testCmd = "runghc -package-conf=dist/package.conf.inplace MakeManPage.hs" -- makes pandoc.1 from README
|
||||
runCommand testCmd >>= waitForProcess >>= exitWith
|
||||
|
|
|
@ -146,13 +146,15 @@ readers :: [(String, ParserState -> String -> Pandoc)]
|
|||
readers = [("native" , \_ -> read)
|
||||
,("json" , \_ -> decodeJSON)
|
||||
,("markdown" , readMarkdown)
|
||||
,("markdown+lhs" , readMarkdown)
|
||||
,("markdown+lhs" , \st ->
|
||||
readMarkdown st{ stateLiterateHaskell = True})
|
||||
,("rst" , readRST)
|
||||
,("textile" , readTextile) -- TODO : textile+lhs
|
||||
,("rst+lhs" , readRST)
|
||||
,("html" , readHtml)
|
||||
,("latex" , readLaTeX)
|
||||
,("latex+lhs" , readLaTeX)
|
||||
,("latex+lhs" , \st ->
|
||||
readLaTeX st{ stateLiterateHaskell = True})
|
||||
]
|
||||
|
||||
-- | Association list of formats and writers (omitting the
|
||||
|
@ -161,21 +163,25 @@ writers :: [ ( String, WriterOptions -> Pandoc -> String ) ]
|
|||
writers = [("native" , writeNative)
|
||||
,("json" , \_ -> encodeJSON)
|
||||
,("html" , writeHtmlString)
|
||||
,("html+lhs" , writeHtmlString)
|
||||
,("html+lhs" , \o ->
|
||||
writeHtmlString o{ writerLiterateHaskell = True })
|
||||
,("s5" , writeHtmlString)
|
||||
,("slidy" , writeHtmlString)
|
||||
,("docbook" , writeDocbook)
|
||||
,("opendocument" , writeOpenDocument)
|
||||
,("latex" , writeLaTeX)
|
||||
,("latex+lhs" , writeLaTeX)
|
||||
,("latex+lhs" , \o ->
|
||||
writeLaTeX o{ writerLiterateHaskell = True })
|
||||
,("context" , writeConTeXt)
|
||||
,("texinfo" , writeTexinfo)
|
||||
,("man" , writeMan)
|
||||
,("markdown" , writeMarkdown)
|
||||
,("markdown+lhs" , writeMarkdown)
|
||||
,("markdown+lhs" , \o ->
|
||||
writeMarkdown o{ writerLiterateHaskell = True })
|
||||
,("plain" , writePlain)
|
||||
,("rst" , writeRST)
|
||||
,("rst+lhs" , writeRST)
|
||||
,("rst+lhs" , \o ->
|
||||
writeRST o{ writerLiterateHaskell = True })
|
||||
,("mediawiki" , writeMediaWiki)
|
||||
,("textile" , writeTextile)
|
||||
,("rtf" , writeRTF)
|
||||
|
|
|
@ -481,6 +481,7 @@ data WriterOptions = WriterOptions
|
|||
, writerUserDataDir :: Maybe FilePath -- ^ Path of user data directory
|
||||
, writerCiteMethod :: CiteMethod -- ^ How to print cites
|
||||
, writerBiblioFiles :: [FilePath] -- ^ Biblio files to use for citations
|
||||
, writerHtml5 :: Bool -- ^ Produce HTML5
|
||||
} deriving Show
|
||||
|
||||
-- | Default writer options.
|
||||
|
@ -510,6 +511,7 @@ defaultWriterOptions =
|
|||
, writerUserDataDir = Nothing
|
||||
, writerCiteMethod = Citeproc
|
||||
, writerBiblioFiles = []
|
||||
, writerHtml5 = False
|
||||
}
|
||||
|
||||
--
|
||||
|
|
|
@ -170,6 +170,7 @@ inTemplate opts tit auths date toc body' newvars =
|
|||
, ("pagetitle", topTitle')
|
||||
, ("title", renderHtmlFragment tit)
|
||||
, ("date", date') ] ++
|
||||
[ ("html5","true") | writerHtml5 opts ] ++
|
||||
(case toc of
|
||||
Just t -> [ ("toc", renderHtmlFragment t)]
|
||||
Nothing -> []) ++
|
||||
|
@ -189,7 +190,12 @@ tableOfContents opts sects = do
|
|||
let tocList = catMaybes contents
|
||||
return $ if null tocList
|
||||
then Nothing
|
||||
else Just $ thediv ! [prefixedId opts' "TOC"] $ unordList tocList
|
||||
else Just $
|
||||
if writerHtml5 opts
|
||||
then tag "nav" ! [prefixedId opts' "TOC"] $
|
||||
unordList tocList
|
||||
else thediv ! [prefixedId opts' "TOC"] $
|
||||
unordList tocList
|
||||
|
||||
-- | Convert section number to string
|
||||
showSecNum :: [Int] -> String
|
||||
|
@ -226,7 +232,9 @@ elementToHtml opts (Sec level num id' title' elements) = do
|
|||
return $ if slides -- S5 gets confused by the extra divs around sections
|
||||
then toHtmlFromList stuff
|
||||
else if writerSectionDivs opts
|
||||
then thediv ! [prefixedId opts id'] << stuff
|
||||
then if writerHtml5 opts
|
||||
then tag "section" << stuff
|
||||
else thediv ! [prefixedId opts id'] << stuff
|
||||
else toHtmlFromList stuff
|
||||
|
||||
-- | Convert list of Note blocks to a footnote <div>.
|
||||
|
@ -296,8 +304,11 @@ blockToHtml opts (Plain lst) = inlineListToHtml opts lst
|
|||
blockToHtml opts (Para [Image txt (s,tit)]) = do
|
||||
img <- inlineToHtml opts (Image txt (s,tit))
|
||||
capt <- inlineListToHtml opts txt
|
||||
return $ thediv ! [theclass "figure"] <<
|
||||
[img, paragraph ! [theclass "caption"] << capt]
|
||||
return $ if writerHtml5 opts
|
||||
then tag "figure" <<
|
||||
[img, tag "figcaption" << capt]
|
||||
else thediv ! [theclass "figure"] <<
|
||||
[img, paragraph ! [theclass "caption"] << capt]
|
||||
blockToHtml opts (Para lst) = inlineListToHtml opts lst >>= (return . paragraph)
|
||||
blockToHtml _ (RawHtml str) = return $ primHtml str
|
||||
blockToHtml _ (HorizontalRule) = return $ hr
|
||||
|
@ -368,7 +379,17 @@ blockToHtml opts (OrderedList (startnum, numstyle, _) lst) = do
|
|||
then [start startnum]
|
||||
else []) ++
|
||||
(if numstyle /= DefaultStyle
|
||||
then [thestyle $ "list-style-type: " ++ numstyle' ++ ";"]
|
||||
then if writerHtml5 opts
|
||||
then [strAttr "type" $
|
||||
case numstyle of
|
||||
Decimal -> "1"
|
||||
LowerAlpha -> "a"
|
||||
UpperAlpha -> "A"
|
||||
LowerRoman -> "i"
|
||||
UpperRoman -> "I"
|
||||
_ -> "1"]
|
||||
else [thestyle $ "list-style-type: " ++
|
||||
numstyle']
|
||||
else [])
|
||||
return $ ordList ! attribs $ contents
|
||||
blockToHtml opts (DefinitionList lst) = do
|
||||
|
@ -381,28 +402,30 @@ blockToHtml opts (DefinitionList lst) = do
|
|||
else []
|
||||
return $ dlist ! attribs << concat contents
|
||||
blockToHtml opts (Table capt aligns widths headers rows') = do
|
||||
let alignStrings = map alignmentToString aligns
|
||||
captionDoc <- if null capt
|
||||
then return noHtml
|
||||
else inlineListToHtml opts capt >>= return . caption
|
||||
let percent w = show (truncate (100*w) :: Integer) ++ "%"
|
||||
let widthAttrs w = if writerHtml5 opts
|
||||
then [thestyle $ "width: " ++ percent w]
|
||||
else [width $ percent w]
|
||||
let coltags = if all (== 0.0) widths
|
||||
then noHtml
|
||||
else concatHtml $ map
|
||||
(\w -> col ! [width $ percent w] $ noHtml) widths
|
||||
(\w -> col ! (widthAttrs w) $ noHtml) widths
|
||||
head' <- if all null headers
|
||||
then return noHtml
|
||||
else liftM (thead <<) $ tableRowToHtml opts alignStrings 0 headers
|
||||
else liftM (thead <<) $ tableRowToHtml opts aligns 0 headers
|
||||
body' <- liftM (tbody <<) $
|
||||
zipWithM (tableRowToHtml opts alignStrings) [1..] rows'
|
||||
zipWithM (tableRowToHtml opts aligns) [1..] rows'
|
||||
return $ table $ captionDoc +++ coltags +++ head' +++ body'
|
||||
|
||||
tableRowToHtml :: WriterOptions
|
||||
-> [String]
|
||||
-> [Alignment]
|
||||
-> Int
|
||||
-> [[Block]]
|
||||
-> State WriterState Html
|
||||
tableRowToHtml opts alignStrings rownum cols' = do
|
||||
tableRowToHtml opts aligns rownum cols' = do
|
||||
let mkcell = if rownum == 0 then th else td
|
||||
let rowclass = case rownum of
|
||||
0 -> "header"
|
||||
|
@ -410,7 +433,7 @@ tableRowToHtml opts alignStrings rownum cols' = do
|
|||
_ -> "even"
|
||||
cols'' <- sequence $ zipWith
|
||||
(\alignment item -> tableItemToHtml opts mkcell alignment item)
|
||||
alignStrings cols'
|
||||
aligns cols'
|
||||
return $ tr ! [theclass rowclass] $ toHtmlFromList cols''
|
||||
|
||||
alignmentToString :: Alignment -> [Char]
|
||||
|
@ -422,12 +445,15 @@ alignmentToString alignment = case alignment of
|
|||
|
||||
tableItemToHtml :: WriterOptions
|
||||
-> (Html -> Html)
|
||||
-> [Char]
|
||||
-> Alignment
|
||||
-> [Block]
|
||||
-> State WriterState Html
|
||||
tableItemToHtml opts tag' align' item = do
|
||||
contents <- blockListToHtml opts item
|
||||
return $ tag' ! [align align'] $ contents
|
||||
let alignAttrs = if writerHtml5 opts
|
||||
then [thestyle $ "align: " ++ alignmentToString align']
|
||||
else [align $ alignmentToString align']
|
||||
return $ tag' ! alignAttrs $ contents
|
||||
|
||||
blockListToHtml :: WriterOptions -> [Block] -> State WriterState Html
|
||||
blockListToHtml opts lst =
|
||||
|
|
|
@ -41,7 +41,7 @@ import System.Exit ( exitWith, ExitCode (..) )
|
|||
import System.FilePath
|
||||
import System.Console.GetOpt
|
||||
import Data.Char ( toLower )
|
||||
import Data.List ( intercalate, isSuffixOf )
|
||||
import Data.List ( intercalate, isSuffixOf, isPrefixOf )
|
||||
import System.Directory ( getAppUserDataDirectory, doesFileExist )
|
||||
import System.IO ( stdout, stderr )
|
||||
import qualified Text.Pandoc.UTF8 as UTF8
|
||||
|
@ -102,6 +102,7 @@ data Opt = Opt
|
|||
, optOffline :: Bool -- ^ Make slideshow accessible offline
|
||||
, optXeTeX :: Bool -- ^ Format latex for xetex
|
||||
, optSmart :: Bool -- ^ Use smart typography
|
||||
, optHtml5 :: Bool -- ^ Produce HTML5 in HTML
|
||||
, optHTMLMathMethod :: HTMLMathMethod -- ^ Method to print HTML math
|
||||
, optReferenceODT :: Maybe FilePath -- ^ Path of reference.odt
|
||||
, optEPUBStylesheet :: Maybe String -- ^ EPUB stylesheet
|
||||
|
@ -142,6 +143,7 @@ defaultOpts = Opt
|
|||
, optOffline = False
|
||||
, optXeTeX = False
|
||||
, optSmart = False
|
||||
, optHtml5 = False
|
||||
, optHTMLMathMethod = PlainMath
|
||||
, optReferenceODT = Nothing
|
||||
, optEPUBStylesheet = Nothing
|
||||
|
@ -226,6 +228,11 @@ options =
|
|||
(\opt -> return opt { optSmart = True }))
|
||||
"" -- "Use smart quotes, dashes, and ellipses"
|
||||
|
||||
, Option "5" ["html5"]
|
||||
(NoArg
|
||||
(\opt -> return opt { optHtml5 = True }))
|
||||
"" -- "Produce HTML5 in HTML output"
|
||||
|
||||
, Option "m" ["latexmathml", "asciimathml"]
|
||||
(OptArg
|
||||
(\arg opt ->
|
||||
|
@ -629,6 +636,7 @@ main = do
|
|||
, optOffline = offline
|
||||
, optXeTeX = xetex
|
||||
, optSmart = smart
|
||||
, optHtml5 = html5
|
||||
, optHTMLMathMethod = mathMethod
|
||||
, optReferenceODT = referenceODT
|
||||
, optEPUBStylesheet = epubStylesheet
|
||||
|
@ -771,7 +779,9 @@ main = do
|
|||
else obfuscationMethod,
|
||||
writerIdentifierPrefix = idPrefix,
|
||||
writerSourceDirectory = sourceDir,
|
||||
writerUserDataDir = datadir }
|
||||
writerUserDataDir = datadir,
|
||||
writerHtml5 = html5 &&
|
||||
"html" `isPrefixOf` writerName' }
|
||||
|
||||
when (isNonTextOutput writerName' && outputFile == "-") $
|
||||
do UTF8.hPutStrLn stderr ("Error: Cannot write " ++ writerName ++ " output to stdout.\n" ++
|
||||
|
|
|
@ -1,14 +1,28 @@
|
|||
$if(html5)$
|
||||
<!DOCTYPE html>
|
||||
<html$if(lang)$ lang="$lang$"$endif$>
|
||||
$else$
|
||||
<!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">
|
||||
<html xmlns="http://www.w3.org/1999/xhtml"$if(lang)$ lang="$lang$" xml:lang="$lang$"$endif$>
|
||||
$endif$
|
||||
<head>
|
||||
<title>$if(title-prefix)$$title-prefix$ - $endif$$if(pagetitle)$$pagetitle$$endif$</title>
|
||||
$if(html5)$
|
||||
<meta charset="utf-8" />
|
||||
$else$
|
||||
<meta http-equiv="Content-Type" content="text/html; charset=utf-8" />
|
||||
$endif$
|
||||
<meta name="generator" content="pandoc" />
|
||||
$for(author)$
|
||||
<meta name="author" content="$author$" />
|
||||
$endfor$
|
||||
$if(date)$
|
||||
<meta name="date" content="$date$" />
|
||||
$endif$
|
||||
<title>$if(title-prefix)$$title-prefix$ - $endif$$if(pagetitle)$$pagetitle$$endif$</title>
|
||||
$if(html5)$
|
||||
<!--[if lt IE 9]>
|
||||
<script src="http://html5shim.googlecode.com/svn/trunk/html5.js"></script>
|
||||
<![endif]-->
|
||||
$endif$
|
||||
$if(highlighting-css)$
|
||||
<style type="text/css">
|
||||
|
@ -16,11 +30,14 @@ $highlighting-css$
|
|||
</style>
|
||||
$endif$
|
||||
$for(css)$
|
||||
<link rel="stylesheet" href="$css$" type="text/css" />
|
||||
<link rel="stylesheet" href="$css$" $if(html5)$$else$type="text/css" $endif$/>
|
||||
$endfor$
|
||||
$if(math)$
|
||||
$if(html5)$
|
||||
$else$
|
||||
$math$
|
||||
$endif$
|
||||
$endif$
|
||||
$for(header-includes)$
|
||||
$header-includes$
|
||||
$endfor$
|
||||
|
@ -30,7 +47,13 @@ $for(include-before)$
|
|||
$include-before$
|
||||
$endfor$
|
||||
$if(title)$
|
||||
$if(html5)$
|
||||
<header>
|
||||
$endif$
|
||||
<h1 class="title">$title$</h1>
|
||||
$if(html5)$
|
||||
</header>
|
||||
$endif$
|
||||
$endif$
|
||||
$if(toc)$
|
||||
$toc$
|
||||
|
|
|
@ -1,7 +1,6 @@
|
|||
<!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">
|
||||
<head>
|
||||
<title>$if(title-prefix)$$title-prefix$ - $endif$$if(pagetitle)$$pagetitle$$endif$</title>
|
||||
<meta http-equiv="Content-Type" content="text/html; charset=utf-8" />
|
||||
<meta name="generator" content="pandoc" />
|
||||
$for(author)$
|
||||
|
@ -10,6 +9,7 @@ $endfor$
|
|||
$if(date)$
|
||||
<meta name="date" content="$date$" />
|
||||
$endif$
|
||||
<title>$if(title-prefix)$$title-prefix$ - $endif$$if(pagetitle)$$pagetitle$$endif$</title>
|
||||
<!-- configuration parameters -->
|
||||
<meta name="defaultView" content="slideshow" />
|
||||
<meta name="controlVis" content="hidden" />
|
||||
|
|
|
@ -3,7 +3,6 @@
|
|||
"http://www.w3.org/TR/xhtml1/DTD/xhtml1-strict.dtd">
|
||||
<html xmlns="http://www.w3.org/1999/xhtml" lang="en" xml:lang="en">
|
||||
<head>
|
||||
<title>$if(title-prefix)$$title-prefix$ - $endif$$if(pagetitle)$$pagetitle$$endif$</title>
|
||||
<meta http-equiv="Content-Type" content="text/html; charset=utf-8" />
|
||||
<meta name="generator" content="pandoc" />
|
||||
$for(author)$
|
||||
|
@ -13,6 +12,7 @@ $if(date)$
|
|||
<meta name="date" content="$date$" />
|
||||
$endif$
|
||||
$if(highlighting-css)$
|
||||
<title>$if(title-prefix)$$title-prefix$ - $endif$$if(pagetitle)$$pagetitle$$endif$</title>
|
||||
<style type="text/css">
|
||||
$highlighting-css$
|
||||
</style>
|
||||
|
|
|
@ -1,12 +1,12 @@
|
|||
<!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">
|
||||
<head>
|
||||
<title>My S5 Document</title>
|
||||
<meta http-equiv="Content-Type" content="text/html; charset=utf-8" />
|
||||
<meta name="generator" content="pandoc" />
|
||||
<meta name="author" content="Sam Smith" />
|
||||
<meta name="author" content="Jen Jones" />
|
||||
<meta name="date" content="July 15, 2006" />
|
||||
<title>My S5 Document</title>
|
||||
<!-- configuration parameters -->
|
||||
<meta name="defaultView" content="slideshow" />
|
||||
<meta name="controlVis" content="hidden" />
|
||||
|
|
|
@ -1,12 +1,12 @@
|
|||
<!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">
|
||||
<head>
|
||||
<title>My S5 Document</title>
|
||||
<meta http-equiv="Content-Type" content="text/html; charset=utf-8" />
|
||||
<meta name="generator" content="pandoc" />
|
||||
<meta name="author" content="Sam Smith" />
|
||||
<meta name="author" content="Jen Jones" />
|
||||
<meta name="date" content="July 15, 2006" />
|
||||
<title>My S5 Document</title>
|
||||
<!-- configuration parameters -->
|
||||
<meta name="defaultView" content="slideshow" />
|
||||
<meta name="controlVis" content="hidden" />
|
||||
|
|
|
@ -1,12 +1,12 @@
|
|||
<!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">
|
||||
<head>
|
||||
<title>My S5 Document</title>
|
||||
<meta http-equiv="Content-Type" content="text/html; charset=utf-8" />
|
||||
<meta name="generator" content="pandoc" />
|
||||
<meta name="author" content="Sam Smith" />
|
||||
<meta name="author" content="Jen Jones" />
|
||||
<meta name="date" content="July 15, 2006" />
|
||||
<title>My S5 Document</title>
|
||||
<link rel="stylesheet" href="main.css" type="text/css" />
|
||||
STUFF INSERTED
|
||||
</head>
|
||||
|
|
|
@ -1,12 +1,12 @@
|
|||
<!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">
|
||||
<head>
|
||||
<title>Pandoc Test Suite</title>
|
||||
<meta http-equiv="Content-Type" content="text/html; charset=utf-8" />
|
||||
<meta name="generator" content="pandoc" />
|
||||
<meta name="author" content="John MacFarlane" />
|
||||
<meta name="author" content="Anonymous" />
|
||||
<meta name="date" content="July 17, 2006" />
|
||||
<title>Pandoc Test Suite</title>
|
||||
</head>
|
||||
<body>
|
||||
<h1 class="title">Pandoc Test Suite</h1>
|
||||
|
@ -74,7 +74,7 @@
|
|||
></pre
|
||||
><p
|
||||
>A list:</p
|
||||
><ol style="list-style-type: decimal;"
|
||||
><ol style="list-style-type: decimal"
|
||||
><li
|
||||
>item one</li
|
||||
><li
|
||||
|
@ -207,7 +207,7 @@ These should not be escaped: \$ \\ \> \[ \{
|
|||
>Ordered</h2
|
||||
><p
|
||||
>Tight:</p
|
||||
><ol style="list-style-type: decimal;"
|
||||
><ol style="list-style-type: decimal"
|
||||
><li
|
||||
>First</li
|
||||
><li
|
||||
|
@ -217,7 +217,7 @@ These should not be escaped: \$ \\ \> \[ \{
|
|||
></ol
|
||||
><p
|
||||
>and:</p
|
||||
><ol style="list-style-type: decimal;"
|
||||
><ol style="list-style-type: decimal"
|
||||
><li
|
||||
>One</li
|
||||
><li
|
||||
|
@ -227,7 +227,7 @@ These should not be escaped: \$ \\ \> \[ \{
|
|||
></ol
|
||||
><p
|
||||
>Loose using tabs:</p
|
||||
><ol style="list-style-type: decimal;"
|
||||
><ol style="list-style-type: decimal"
|
||||
><li
|
||||
><p
|
||||
>First</p
|
||||
|
@ -243,7 +243,7 @@ These should not be escaped: \$ \\ \> \[ \{
|
|||
></ol
|
||||
><p
|
||||
>and using spaces:</p
|
||||
><ol style="list-style-type: decimal;"
|
||||
><ol style="list-style-type: decimal"
|
||||
><li
|
||||
><p
|
||||
>One</p
|
||||
|
@ -259,7 +259,7 @@ These should not be escaped: \$ \\ \> \[ \{
|
|||
></ol
|
||||
><p
|
||||
>Multiple paragraphs:</p
|
||||
><ol style="list-style-type: decimal;"
|
||||
><ol style="list-style-type: decimal"
|
||||
><li
|
||||
><p
|
||||
>Item 1, graf one.</p
|
||||
|
@ -291,7 +291,7 @@ These should not be escaped: \$ \\ \> \[ \{
|
|||
></ul
|
||||
><p
|
||||
>Here’s another:</p
|
||||
><ol style="list-style-type: decimal;"
|
||||
><ol style="list-style-type: decimal"
|
||||
><li
|
||||
>First</li
|
||||
><li
|
||||
|
@ -309,7 +309,7 @@ These should not be escaped: \$ \\ \> \[ \{
|
|||
></ol
|
||||
><p
|
||||
>Same thing but with paragraphs:</p
|
||||
><ol style="list-style-type: decimal;"
|
||||
><ol style="list-style-type: decimal"
|
||||
><li
|
||||
><p
|
||||
>First</p
|
||||
|
@ -355,7 +355,7 @@ These should not be escaped: \$ \\ \> \[ \{
|
|||
></ul
|
||||
><h2 id="fancy-list-markers"
|
||||
>Fancy list markers</h2
|
||||
><ol start="2" style="list-style-type: decimal;"
|
||||
><ol start="2" style="list-style-type: decimal"
|
||||
><li
|
||||
>begins with 2</li
|
||||
><li
|
||||
|
@ -363,11 +363,11 @@ These should not be escaped: \$ \\ \> \[ \{
|
|||
>and now 3</p
|
||||
><p
|
||||
>with a continuation</p
|
||||
><ol start="4" style="list-style-type: lower-roman;"
|
||||
><ol start="4" style="list-style-type: lower-roman"
|
||||
><li
|
||||
>sublist with roman numerals, starting with 4</li
|
||||
><li
|
||||
>more items<ol style="list-style-type: upper-alpha;"
|
||||
>more items<ol style="list-style-type: upper-alpha"
|
||||
><li
|
||||
>a subsublist</li
|
||||
><li
|
||||
|
@ -379,13 +379,13 @@ These should not be escaped: \$ \\ \> \[ \{
|
|||
></ol
|
||||
><p
|
||||
>Nesting:</p
|
||||
><ol style="list-style-type: upper-alpha;"
|
||||
><ol style="list-style-type: upper-alpha"
|
||||
><li
|
||||
>Upper Alpha<ol style="list-style-type: upper-roman;"
|
||||
>Upper Alpha<ol style="list-style-type: upper-roman"
|
||||
><li
|
||||
>Upper Roman.<ol start="6" style="list-style-type: decimal;"
|
||||
>Upper Roman.<ol start="6" style="list-style-type: decimal"
|
||||
><li
|
||||
>Decimal start with 6<ol start="3" style="list-style-type: lower-alpha;"
|
||||
>Decimal start with 6<ol start="3" style="list-style-type: lower-alpha"
|
||||
><li
|
||||
>Lower alpha with paren</li
|
||||
></ol
|
||||
|
@ -559,7 +559,7 @@ These should not be escaped: \$ \\ \> \[ \{
|
|||
><dd
|
||||
><p
|
||||
>orange fruit</p
|
||||
><ol style="list-style-type: decimal;"
|
||||
><ol style="list-style-type: decimal"
|
||||
><li
|
||||
>sublist</li
|
||||
><li
|
||||
|
@ -1110,7 +1110,7 @@ document.write('<a h'+'ref'+'="ma'+'ilto'+':'+e+'">'+'<code>'+e+'</code>'+'<\/'+
|
|||
></sup
|
||||
></p
|
||||
></blockquote
|
||||
><ol style="list-style-type: decimal;"
|
||||
><ol style="list-style-type: decimal"
|
||||
><li
|
||||
>And in list items.<sup
|
||||
><a href="#fn5" class="footnoteRef" id="fnref5"
|
||||
|
|
Loading…
Add table
Reference in a new issue