Merge pull request #1495 from jkr/inline-drawings

Docx reader: Inline image fix
This commit is contained in:
John MacFarlane 2014-08-07 13:41:58 -07:00
commit 44dad52866
6 changed files with 30 additions and 4 deletions

View file

@ -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,

View file

@ -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

View file

@ -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

View file

@ -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"

Binary file not shown.

View file

@ -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."]]