From 33ff2fed2171fb8b8267e9fff5fbff27d047dd96 Mon Sep 17 00:00:00 2001
From: John MacFarlane <jgm@berkeley.edu>
Date: Tue, 11 Jan 2011 20:23:43 -0800
Subject: [PATCH 1/4] Text.Pandoc:  Improved readers, writers lists for lhs
 variants.

Now the lhs variants set the needed literate Haskell flag in
parser state and writer options.
---
 src/Text/Pandoc.hs | 18 ++++++++++++------
 1 file changed, 12 insertions(+), 6 deletions(-)

diff --git a/src/Text/Pandoc.hs b/src/Text/Pandoc.hs
index c752ffede..3532c1d4b 100644
--- a/src/Text/Pandoc.hs
+++ b/src/Text/Pandoc.hs
@@ -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)

From 6b1407d2090057bb951ecd0b239b659c138cc6b8 Mon Sep 17 00:00:00 2001
From: John MacFarlane <jgm@berkeley.edu>
Date: Tue, 11 Jan 2011 20:34:49 -0800
Subject: [PATCH 2/4] Setup.hs: -Wall clean.

---
 Setup.hs | 6 +++---
 1 file changed, 3 insertions(+), 3 deletions(-)

diff --git a/Setup.hs b/Setup.hs
index b68435216..455909795 100644
--- a/Setup.hs
+++ b/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
@@ -55,8 +55,8 @@ runTestSuite _ _ 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

From e8ad4ba43c7c187a5b6ee6025bc6039488d7f420 Mon Sep 17 00:00:00 2001
From: John MacFarlane <jgm@berkeley.edu>
Date: Tue, 11 Jan 2011 20:37:06 -0800
Subject: [PATCH 3/4] Preliminary support for HTML5.

+ Added writerHtml5 writer option.
+ Added --html5 option.
+ Added support for lang in html tag (so you can do
  'pandoc -s --V lang=en', for example).
+ Updated html template with conditionals for HTML5.
+ When HTML5 selected, use <header> tag around title in document,
  and use <section> tags instead of <div>s if --section-divs
  specified.
---
 README                          | 16 ++++++++++++----
 src/Text/Pandoc/Shared.hs       |  2 ++
 src/Text/Pandoc/Writers/HTML.hs |  5 ++++-
 src/pandoc.hs                   | 11 ++++++++++-
 templates/html.template         | 19 +++++++++++++++++--
 5 files changed, 45 insertions(+), 8 deletions(-)

diff --git a/README b/README
index 1647ef4a9..f6d82e193 100644
--- a/README
+++ b/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`, `epub`, `s5`, and `slidy`.
+
 `-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.
 
diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs
index cc94cf635..f757f4479 100644
--- a/src/Text/Pandoc/Shared.hs
+++ b/src/Text/Pandoc/Shared.hs
@@ -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
                 }
 
 --
diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs
index b8da4bec0..c61387fa7 100644
--- a/src/Text/Pandoc/Writers/HTML.hs
+++ b/src/Text/Pandoc/Writers/HTML.hs
@@ -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 -> [])  ++
@@ -226,7 +227,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>.
diff --git a/src/pandoc.hs b/src/pandoc.hs
index 8811e6816..0e57f8eb7 100644
--- a/src/pandoc.hs
+++ b/src/pandoc.hs
@@ -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,8 @@ main = do
                                                                   else obfuscationMethod,
                                       writerIdentifierPrefix = idPrefix,
                                       writerSourceDirectory  = sourceDir,
-                                      writerUserDataDir      = datadir }
+                                      writerUserDataDir      = datadir,
+                                      writerHtml5            = html5 }
 
   when (isNonTextOutput writerName' && outputFile == "-") $
     do UTF8.hPutStrLn stderr ("Error:  Cannot write " ++ writerName ++ " output to stdout.\n" ++
diff --git a/templates/html.template b/templates/html.template
index bd1864ff0..eabda4f44 100644
--- a/templates/html.template
+++ b/templates/html.template
@@ -1,8 +1,17 @@
+$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$" />
@@ -16,7 +25,7 @@ $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)$
   $math$
@@ -30,7 +39,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$

From 91510a109f9284934fd5b6386fa23a5fc37b09bb Mon Sep 17 00:00:00 2001
From: John MacFarlane <jgm@berkeley.edu>
Date: Tue, 11 Jan 2011 22:25:57 -0800
Subject: [PATCH 4/4] Improvements to --html5 support:

+ <nav> for TOC, <figure> for figures, type attribute in <ol>.
+ Don't add math javascript in html5.
+ Use style attributes instead of deprecated width, align.
+ html template: move <title> after <meta>.
  Note: charset needs to be declared before title.
+ slidy and s5 templates: move <title> after <meta>.
+ html template: Added link to html5 shim for IE.
+ Make --html5 have an effect only for 'html' writer (not s5, slidy, epub).
---
 README                          |  2 +-
 src/Text/Pandoc/Writers/HTML.hs | 49 ++++++++++++++++++++++++---------
 src/pandoc.hs                   |  5 ++--
 templates/html.template         | 10 ++++++-
 templates/s5.template           |  2 +-
 templates/slidy.template        |  2 +-
 tests/s5.basic.html             |  2 +-
 tests/s5.fancy.html             |  2 +-
 tests/s5.inserts.html           |  2 +-
 tests/writer.html               | 36 ++++++++++++------------
 10 files changed, 72 insertions(+), 40 deletions(-)

diff --git a/README b/README
index f6d82e193..07f2266af 100644
--- a/README
+++ b/README
@@ -210,7 +210,7 @@ Options
 
 `-5`, `--html5`
 :   Produce HTML5 instead of HTML4.  This option has no effect for writers
-    other than `html`, `epub`, `s5`, and `slidy`.
+    other than `html`.
 
 `-m` *URL*, `--latexmathml=`*URL*
 :   Use the [LaTeXMathML] script to display embedded TeX math in HTML output.
diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs
index c61387fa7..901575434 100644
--- a/src/Text/Pandoc/Writers/HTML.hs
+++ b/src/Text/Pandoc/Writers/HTML.hs
@@ -190,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
@@ -299,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
@@ -371,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
@@ -384,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"
@@ -413,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]
@@ -425,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 = 
diff --git a/src/pandoc.hs b/src/pandoc.hs
index 0e57f8eb7..2068f5fc6 100644
--- a/src/pandoc.hs
+++ b/src/pandoc.hs
@@ -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
@@ -780,7 +780,8 @@ main = do
                                       writerIdentifierPrefix = idPrefix,
                                       writerSourceDirectory  = sourceDir,
                                       writerUserDataDir      = datadir,
-                                      writerHtml5            = html5 }
+                                      writerHtml5            = html5 &&
+                                                               "html" `isPrefixOf` writerName' }
 
   when (isNonTextOutput writerName' && outputFile == "-") $
     do UTF8.hPutStrLn stderr ("Error:  Cannot write " ++ writerName ++ " output to stdout.\n" ++
diff --git a/templates/html.template b/templates/html.template
index eabda4f44..3f8b76fed 100644
--- a/templates/html.template
+++ b/templates/html.template
@@ -6,7 +6,6 @@ $else$
 <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$
@@ -18,6 +17,12 @@ $for(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">
@@ -28,8 +33,11 @@ $for(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$
diff --git a/templates/s5.template b/templates/s5.template
index 480c1e435..c1f727f6e 100644
--- a/templates/s5.template
+++ b/templates/s5.template
@@ -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" />
diff --git a/templates/slidy.template b/templates/slidy.template
index f625c36e2..9cfdb8f5e 100644
--- a/templates/slidy.template
+++ b/templates/slidy.template
@@ -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>
diff --git a/tests/s5.basic.html b/tests/s5.basic.html
index 825d05868..64971417a 100644
--- a/tests/s5.basic.html
+++ b/tests/s5.basic.html
@@ -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" />
diff --git a/tests/s5.fancy.html b/tests/s5.fancy.html
index f4f2e7815..200990b6a 100644
--- a/tests/s5.fancy.html
+++ b/tests/s5.fancy.html
@@ -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" />
diff --git a/tests/s5.inserts.html b/tests/s5.inserts.html
index 90014f2e6..3010ef758 100644
--- a/tests/s5.inserts.html
+++ b/tests/s5.inserts.html
@@ -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>
diff --git a/tests/writer.html b/tests/writer.html
index 39ae2ebb7..ae83dc20f 100644
--- a/tests/writer.html
+++ b/tests/writer.html
@@ -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:  \$ \\ \&gt; \[ \{
 >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:  \$ \\ \&gt; \[ \{
   ></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:  \$ \\ \&gt; \[ \{
   ></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:  \$ \\ \&gt; \[ \{
   ></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:  \$ \\ \&gt; \[ \{
   ></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:  \$ \\ \&gt; \[ \{
   ></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:  \$ \\ \&gt; \[ \{
   ></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:  \$ \\ \&gt; \[ \{
   ></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:  \$ \\ \&gt; \[ \{
     >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:  \$ \\ \&gt; \[ \{
   ></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:  \$ \\ \&gt; \[ \{
   ><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"