diff --git a/pandoc.cabal b/pandoc.cabal
index b30ce37aa..66b4d61c4 100644
--- a/pandoc.cabal
+++ b/pandoc.cabal
@@ -178,6 +178,7 @@ Extra-Source-Files:
                  tests/docx.hanging_indent.docx,
                  tests/docx.headers.docx,
                  tests/docx.image.docx,
+                 tests/docx.inline_images.docx,
                  tests/docx.inline_code.docx,
                  tests/docx.inline_formatting.docx,
                  tests/docx.links.docx,
diff --git a/src/Text/Pandoc/Readers/Docx.hs b/src/Text/Pandoc/Readers/Docx.hs
index 367e26bd0..f19570aec 100644
--- a/src/Text/Pandoc/Readers/Docx.hs
+++ b/src/Text/Pandoc/Readers/Docx.hs
@@ -321,6 +321,13 @@ runToInlines (Footnote bps) =
   concatMapM bodyPartToBlocks bps >>= (\blks -> return [Note blks])
 runToInlines (Endnote bps) =
   concatMapM bodyPartToBlocks bps >>= (\blks -> return [Note blks])
+runToInlines (InlineDrawing fp bs) = do
+  mediaBag <- gets docxMediaBag
+  modify $ \s -> s { docxMediaBag = insertMedia fp Nothing bs mediaBag }
+  return [Image [] (fp, "")]
+
+  
+
 
 parPartToInlines :: ParPart -> DocxContext [Inline]
 parPartToInlines (PlainRun r) = runToInlines r
diff --git a/src/Text/Pandoc/Readers/Docx/Parse.hs b/src/Text/Pandoc/Readers/Docx/Parse.hs
index 96210c31a..bc4e6ea06 100644
--- a/src/Text/Pandoc/Readers/Docx/Parse.hs
+++ b/src/Text/Pandoc/Readers/Docx/Parse.hs
@@ -282,6 +282,7 @@ defaultGroupStyle = GroupStyle {groupChr = Nothing, groupPos = Nothing}
 data Run = Run RunStyle [RunElem]
          | Footnote [BodyPart]
          | Endnote [BodyPart]
+         | InlineDrawing FilePath B.ByteString
            deriving Show
 
 data RunElem = TextRun String | LnBrk | Tab
@@ -874,14 +875,14 @@ lookupRelationship :: RelId -> [Relationship] -> Maybe Target
 lookupRelationship relid rels =
   lookup relid (map (\(Relationship pair) -> pair) rels)
 
-expandDrawingId :: String -> D ParPart
+expandDrawingId :: String -> D (FilePath, B.ByteString)
 expandDrawingId s = do
   target <- asks (lookupRelationship s . envRelationships)
   case target of
     Just filepath -> do
       bytes <- asks (lookup (combine "word" filepath) . envMedia)
       case bytes of
-        Just bs -> return $ Drawing filepath bs
+        Just bs -> return (filepath, bs)
         Nothing -> throwError DocxError
     Nothing -> throwError DocxError
 
@@ -894,7 +895,7 @@ elemToParPart ns element
                   >>= findAttr (QName "embed" (lookup "r" ns) (Just "r"))
     in
      case drawing of
-       Just s -> expandDrawingId s
+       Just s -> expandDrawingId s >>= (\(fp, bs) -> return $ Drawing fp bs)
        Nothing -> throwError WrongElem
 elemToParPart ns element
   | isElem ns "w" "r" element =
@@ -943,6 +944,17 @@ lookupEndnote :: String -> Notes -> Maybe Element
 lookupEndnote s (Notes _ _ ens) = ens >>= (M.lookup s)
 
 elemToRun :: NameSpaces -> Element -> D Run
+elemToRun ns element
+  | isElem ns "w" "r" element
+  , Just drawingElem <- findChild (elemName ns "w" "drawing") element =
+    let a_ns = "http://schemas.openxmlformats.org/drawingml/2006/main"
+        drawing = findElement (QName "blip" (Just a_ns) (Just "a")) drawingElem
+                  >>= findAttr (QName "embed" (lookup "r" ns) (Just "r"))
+    in
+     case drawing of
+       Just s -> expandDrawingId s >>=
+                 (\(fp, bs) -> return $ InlineDrawing fp bs)
+       Nothing -> throwError WrongElem
 elemToRun ns element
   | isElem ns "w" "r" element
   , Just ref <- findChild (elemName ns "w" "footnoteReference") element
diff --git a/tests/Tests/Readers/Docx.hs b/tests/Tests/Readers/Docx.hs
index efc520dba..c310cc8d7 100644
--- a/tests/Tests/Readers/Docx.hs
+++ b/tests/Tests/Readers/Docx.hs
@@ -107,9 +107,13 @@ tests = [ testGroup "inlines"
             "docx.links.docx"
             "docx.links.native"
           , testCompare
-            "inline image with reference output"
+            "inline image"
             "docx.image.docx"
             "docx.image_no_embed.native"
+          , testCompare
+            "inline image in links"
+            "docx.inline_images.docx"
+            "docx.inline_images.native"
           , testCompare
             "handling unicode input"
             "docx.unicode.docx"
diff --git a/tests/docx.inline_images.docx b/tests/docx.inline_images.docx
new file mode 100644
index 000000000..6288f66ff
Binary files /dev/null and b/tests/docx.inline_images.docx differ
diff --git a/tests/docx.inline_images.native b/tests/docx.inline_images.native
new file mode 100644
index 000000000..f962f5c09
--- /dev/null
+++ b/tests/docx.inline_images.native
@@ -0,0 +1,2 @@
+[Para [Str "This",Space,Str "picture",Space,Image [] ("media/image1.jpg",""),Space,Str "is",Space,Str "an",Space,Str "identicon."]
+,Para [Str "Here",Space,Str "is",Space,Link [Str "one",Space,Image [] ("media/image2.jpg",""),Space,Str "that"] ("http://www.google.com",""),Space,Str "links."]]