diff --git a/pandoc.cabal b/pandoc.cabal
index 3818d0bf4..114ac5227 100644
--- a/pandoc.cabal
+++ b/pandoc.cabal
@@ -125,6 +125,7 @@ Extra-Source-Files:
                  tests/bodybg.gif
                  tests/*.native
                  tests/docbook-reader.docbook
+                 tests/docbook-xref.docbook
                  tests/html-reader.html
                  tests/opml-reader.opml
                  tests/haddock-reader.haddock
diff --git a/src/Text/Pandoc/Readers/DocBook.hs b/src/Text/Pandoc/Readers/DocBook.hs
index 352b94496..9243221f0 100644
--- a/src/Text/Pandoc/Readers/DocBook.hs
+++ b/src/Text/Pandoc/Readers/DocBook.hs
@@ -18,6 +18,7 @@ import Text.TeXMath (readMathML, writeTeX)
 import Text.Pandoc.Error (PandocError)
 import Text.Pandoc.Compat.Except
 import Data.Default
+import Data.Foldable (asum)
 
 {-
 
@@ -498,7 +499,7 @@ List of all DocBook tags, with [x] indicating implemented,
 [x] warning - An admonition set off from the text
 [x] wordasword - A word meant specifically as a word and not representing
     anything else
-[ ] xref - A cross reference to another part of the document
+[x] xref - A cross reference to another part of the document
 [ ] year - The year of publication of a document
 [x] ?asciidoc-br? - line break from asciidoc docbook output
 -}
@@ -511,6 +512,7 @@ data DBState = DBState{ dbSectionLevel :: Int
                       , dbAcceptsMeta  :: Bool
                       , dbBook         :: Bool
                       , dbFigureTitle  :: Inlines
+                      , dbContent      :: [Content]
                       } deriving Show
 
 instance Default DBState where
@@ -519,13 +521,14 @@ instance Default DBState where
                , dbMeta = mempty
                , dbAcceptsMeta = False
                , dbBook = False
-               , dbFigureTitle = mempty }
+               , dbFigureTitle = mempty
+               , dbContent = [] }
 
 
 readDocBook :: ReaderOptions -> String -> Either PandocError Pandoc
 readDocBook _ inp  = (\blocks -> Pandoc (dbMeta st') (toList . mconcat $ blocks)) <$>  bs
-  where (bs , st') = flip runState def . runExceptT . mapM parseBlock . normalizeTree . parseXML $ inp'
-        inp' = handleInstructions inp
+  where (bs , st') = flip runState (def{ dbContent = tree }) . runExceptT . mapM parseBlock $ tree
+        tree = normalizeTree . parseXML . handleInstructions $ inp
 
 -- We treat <?asciidoc-br?> specially (issue #1236), converting it
 -- to <br/>, since xml-light doesn't parse the instruction correctly.
@@ -950,7 +953,13 @@ parseInline (Elem e) =
         "keycombo" -> keycombo <$> (mapM parseInline $ elContent e)
         "menuchoice" -> menuchoice <$> (mapM parseInline $
                                         filter isGuiMenu $ elContent e)
-        "xref" -> return $ str "?" -- so at least you know something is there
+        "xref" -> do
+            content <- dbContent <$> get
+            let linkend = attrValue "linkend" e
+            let title = case attrValue "endterm" e of
+                            ""      -> maybe "???" xrefTitleByElem (findElementById linkend content)
+                            endterm -> maybe "???" strContent (findElementById endterm content)
+            return $ link ('#' : linkend) "" (singleton (Str title))
         "email" -> return $ link ("mailto:" ++ strContent e) ""
                           $ str $ strContent e
         "uri" -> return $ link (strContent e) "" $ str $ strContent e
@@ -1011,3 +1020,26 @@ parseInline (Elem e) =
          isGuiMenu (Elem x) = named "guimenu" x || named "guisubmenu" x ||
                               named "guimenuitem" x
          isGuiMenu _        = False
+
+         findElementById idString content
+            = asum [filterElement (\x -> attrValue "id" x == idString) el | Elem el <- content]
+
+         -- Use the 'xreflabel' attribute for getting the title of a xref link;
+         -- if there's no such attribute, employ some heuristics based on what
+         -- docbook-xsl does.
+         xrefTitleByElem el
+             | not (null xrefLabel) = xrefLabel
+             | otherwise            = case qName (elName el) of
+                  "chapter"      -> descendantContent "title" el
+                  "sect1"        -> descendantContent "title" el
+                  "sect2"        -> descendantContent "title" el
+                  "sect3"        -> descendantContent "title" el
+                  "sect4"        -> descendantContent "title" el
+                  "sect5"        -> descendantContent "title" el
+                  "cmdsynopsis"  -> descendantContent "command" el
+                  "funcsynopsis" -> descendantContent "function" el
+                  _              -> qName (elName el) ++ "_title"
+          where
+            xrefLabel = attrValue "xreflabel" el
+            descendantContent name = maybe "???" strContent
+                                   . findElement (QName name Nothing Nothing)
diff --git a/tests/Tests/Old.hs b/tests/Tests/Old.hs
index 047ad0481..5cfee9f76 100644
--- a/tests/Tests/Old.hs
+++ b/tests/Tests/Old.hs
@@ -105,6 +105,8 @@ tests = [ testGroup "markdown"
           [ testGroup "writer" $ writerTests "docbook"
           , test "reader" ["-r", "docbook", "-w", "native", "-s"]
             "docbook-reader.docbook" "docbook-reader.native"
+          , test "reader" ["-r", "docbook", "-w", "native", "-s"]
+            "docbook-xref.docbook" "docbook-xref.native"
           ]
         , testGroup "native"
           [ testGroup "writer" $ writerTests "native"
diff --git a/tests/docbook-xref.docbook b/tests/docbook-xref.docbook
new file mode 100644
index 000000000..ebcd94d00
--- /dev/null
+++ b/tests/docbook-xref.docbook
@@ -0,0 +1,70 @@
+<!DOCTYPE book PUBLIC "-//OASIS//DTD DocBook XML V4.1.2//EN"
+          "http://www.oasis-open.org/docbook/xml/4.1.2/docbookx.dtd">
+<book><title>An Example Book</title>
+<chapter id="ch01"><title>XRef Samples</title>
+<para>
+This paragraph demonstrates several features of
+<sgmltag>XRef</sgmltag>.
+</para>
+<itemizedlist>
+<listitem><para>A straight link generates the
+cross-reference text: <xref linkend="ch02"/>.
+</para></listitem>
+<listitem><para>A link to an element with an
+<sgmltag class="attribute">XRefLabel</sgmltag>:
+<xref linkend="ch03"/>.
+</para></listitem>
+<listitem><para>A link with an
+<sgmltag class="attribute">EndTerm</sgmltag>:
+<xref linkend="ch04" endterm="ch04short"/>.
+</para></listitem>
+<listitem><para>A link to an
+<sgmltag>cmdsynopsis</sgmltag> element: <xref linkend="cmd01"/>.
+</para></listitem>
+<listitem><para>A link to an
+<sgmltag>funcsynopsis</sgmltag> element: <xref linkend="func01"/>.
+</para></listitem>
+</itemizedlist>
+</chapter>
+
+<chapter id="ch02">
+  <title>The Second Chapter</title>
+  <para>Some content here</para>
+</chapter>
+
+<chapter id="ch03" xreflabel="Chapter the Third">
+  <title>The Third Chapter</title>
+  <para>Some content here</para>
+</chapter>
+
+<chapter id="ch04">
+  <title>The Fourth Chapter</title>
+  <titleabbrev id="ch04short">Chapter 4</titleabbrev>
+  <para>Some content here</para>
+
+<cmdsynopsis id="cmd01">
+  <command>chgrp</command>
+  <arg>-R
+    <group>
+      <arg>-H</arg>
+      <arg>-L</arg>
+      <arg>-P</arg>
+    </group>
+  </arg>
+  <arg>-f</arg>
+  <arg choice='plain'><replaceable>group</replaceable></arg>
+  <arg rep='repeat' choice='plain'><replaceable>file</replaceable></arg>
+</cmdsynopsis>
+
+
+<funcsynopsis id="func01">
+<funcprototype>
+<funcdef>int <function>max</function></funcdef>
+<paramdef>int <parameter>int1</parameter></paramdef>
+<paramdef>int <parameter>int2</parameter></paramdef>
+</funcprototype>
+</funcsynopsis>
+
+</chapter>
+</book>
+
diff --git a/tests/docbook-xref.native b/tests/docbook-xref.native
new file mode 100644
index 000000000..ec870842b
--- /dev/null
+++ b/tests/docbook-xref.native
@@ -0,0 +1,29 @@
+Pandoc (Meta {unMeta = fromList []})
+[Header 1 ("ch01",[],[]) [Str "XRef",Space,Str "Samples"]
+,Para [Str "This",Space,Str "paragraph",Space,Str "demonstrates",Space,Str "several",Space,Str "features",Space,Str "of",Space,Str "XRef."]
+,BulletList
+ [[Para [Str "A",Space,Str "straight",Space,Str "link",Space,Str "generates",Space,Str "the",Space,Str "cross-reference",Space,Str "text:",Space,Link [Str "The Second Chapter"] ("#ch02",""),Str "."]]
+ ,[Para [Str "A",Space,Str "link",Space,Str "to",Space,Str "an",Space,Str "element",Space,Str "with",Space,Str "an",Space,Str "XRefLabel:",Space,Link [Str "Chapter the Third"] ("#ch03",""),Str "."]]
+ ,[Para [Str "A",Space,Str "link",Space,Str "with",Space,Str "an",Space,Str "EndTerm:",Space,Link [Str "Chapter 4"] ("#ch04",""),Str "."]]
+ ,[Para [Str "A",Space,Str "link",Space,Str "to",Space,Str "an",Space,Str "cmdsynopsis",Space,Str "element:",Space,Link [Str "chgrp"] ("#cmd01",""),Str "."]]
+ ,[Para [Str "A",Space,Str "link",Space,Str "to",Space,Str "an",Space,Str "funcsynopsis",Space,Str "element:",Space,Link [Str "max"] ("#func01",""),Str "."]]]
+,Header 1 ("ch02",[],[]) [Str "The",Space,Str "Second",Space,Str "Chapter"]
+,Para [Str "Some",Space,Str "content",Space,Str "here"]
+,Header 1 ("ch03",[],[]) [Str "The",Space,Str "Third",Space,Str "Chapter"]
+,Para [Str "Some",Space,Str "content",Space,Str "here"]
+,Header 1 ("ch04",[],[]) [Str "The",Space,Str "Fourth",Space,Str "Chapter"]
+,Para [Str "Some",Space,Str "content",Space,Str "here"]
+,Plain [Str "chgrp"]
+,Plain [Str "-R"]
+,Plain [Str "-H"]
+,Plain [Str "-L"]
+,Plain [Str "-P"]
+,Plain [Str "-f"]
+,Plain [Str "group"]
+,Plain [Str "file"]
+,Plain [Str "int"]
+,Plain [Str "max"]
+,Plain [Str "int"]
+,Plain [Str "int1"]
+,Plain [Str "int"]
+,Plain [Str "int2"]]