diff --git a/README b/README
index e2a25e2f2..287c0c4b0 100644
--- a/README
+++ b/README
@@ -544,9 +544,10 @@ Math rendering in HTML
     so it can be cached.
 
 `--mathml`[=*URL*]
-:   Convert TeX math to MathML.  In standalone mode, a small javascript
-    (or a link to such a script if a *URL* is supplied) will be inserted that
-    allows the MathML to be viewed on some browsers.
+:   Convert TeX math to MathML (works with `docbook` as well as `html`).
+    In standalone mode, a small javascript (or a link to such a script if a
+    *URL* is supplied) will be inserted that allows the MathML to be viewed on
+    some browsers.
 
 `--jsmath`[=*URL*]
 :   Use [jsMath] to display embedded TeX math in HTML output.
@@ -1652,10 +1653,15 @@ MediaWiki
 Textile
   ~ It will be rendered inside `<span class="math">` tags.
 
-RTF, DocBook, OpenDocument, ODT
+RTF, OpenDocument, ODT
   ~ It will be rendered, if possible, using unicode characters,
     and will otherwise appear verbatim.
 
+Docbook
+  ~ If the `--mathml` flag is used, it will be rendered using mathml
+    in an `inlineequation` or `informalequation` tag.  Otherwise it
+    will be rendered, if possible, using unicode characters.
+
 Docx
   ~ It will be rendered using OMML math markup.
 
diff --git a/src/Text/Pandoc/Writers/Docbook.hs b/src/Text/Pandoc/Writers/Docbook.hs
index 878d2face..1bcf99dcf 100644
--- a/src/Text/Pandoc/Writers/Docbook.hs
+++ b/src/Text/Pandoc/Writers/Docbook.hs
@@ -37,6 +37,9 @@ import Data.List ( isPrefixOf, intercalate, isSuffixOf )
 import Data.Char ( toLower )
 import Text.Pandoc.Highlighting ( languages, languagesByExtension )
 import Text.Pandoc.Pretty
+import Text.TeXMath
+import qualified Text.XML.Light as Xml
+import Data.Generics (everywhere, mkT)
 
 -- | Convert list of authors to a docbook <author> section
 authorToDocbook :: WriterOptions -> [Inline] -> Doc
@@ -79,7 +82,10 @@ writeDocbook opts (Pandoc (Meta tit auths dat) blocks) =
                 [ ("body", main)
                 , ("title", render' title)
                 , ("date", render' date) ] ++
-                [ ("author", render' a) | a <- authors ]
+                [ ("author", render' a) | a <- authors ] ++
+                [ ("mathml", "yes") | case writerHTMLMathMethod opts of
+                                            MathML _ -> True
+                                            _ -> False ]
   in  if writerStandalone opts
          then renderTemplate context $ writerTemplate opts
          else main
@@ -252,7 +258,23 @@ inlineToDocbook opts (Cite _ lst) =
   inlinesToDocbook opts lst 
 inlineToDocbook _ (Code _ str) = 
   inTagsSimple "literal" $ text (escapeStringForXML str)
-inlineToDocbook opts (Math _ str) = inlinesToDocbook opts $ readTeXMath str
+inlineToDocbook opts (Math t str)
+  | isMathML (writerHTMLMathMethod opts) =
+    case texMathToMathML dt str of
+      Right r -> inTagsSimple tagtype
+                 $ text $ Xml.ppcElement conf
+                 $ fixNS
+                 $ removeAttr r
+      Left  _ -> inlinesToDocbook opts
+                 $ readTeXMath str
+  | otherwise = inlinesToDocbook opts $ readTeXMath str
+     where (dt, tagtype) = case t of
+                            InlineMath  -> (DisplayInline,"inlineequation")
+                            DisplayMath -> (DisplayBlock,"informalequation")
+           conf = Xml.useShortEmptyTags (const False) Xml.defaultConfigPP
+           removeAttr e = e{ Xml.elAttribs = [] }
+           fixNS' qname = qname{ Xml.qPrefix = Just "mml" }
+           fixNS = everywhere (mkT fixNS')
 inlineToDocbook _ (RawInline f x) | f == "html" || f == "docbook" = text x
                                   | otherwise                     = empty
 inlineToDocbook _ LineBreak = inTagsSimple "literallayout" empty
@@ -279,3 +301,7 @@ inlineToDocbook _ (Image _ (src, tit)) =
       titleDoc $$ selfClosingTag "imagedata" [("fileref", src)]
 inlineToDocbook opts (Note contents) = 
   inTagsIndented "footnote" $ blocksToDocbook opts contents
+
+isMathML :: HTMLMathMethod -> Bool
+isMathML (MathML _) = True
+isMathML _          = False
diff --git a/templates b/templates
index f26a6351b..633da96f9 160000
--- a/templates
+++ b/templates
@@ -1 +1 @@
-Subproject commit f26a6351b20dff374b0209a1140faf1f7aeb5f74
+Subproject commit 633da96f9870c781b9bdf913881a4eac4a0fa3a2