From c924611de526601f64154bef83035f75e8f4c334 Mon Sep 17 00:00:00 2001
From: Hubert Plociniczak <hubert.plociniczak@gmail.com>
Date: Wed, 12 Oct 2016 17:42:30 +0200
Subject: Basic support for images in ODT documents

Highly influenced by the docx support, refactored
some code to avoid DRY.
---
 src/Text/Pandoc/Readers/Docx/Parse.hs        | 20 ++-----
 src/Text/Pandoc/Readers/Odt.hs               | 44 +++++++++-----
 src/Text/Pandoc/Readers/Odt/ContentReader.hs | 89 ++++++++++++++++++++++++++--
 src/Text/Pandoc/Shared.hs                    | 16 +++++
 4 files changed, 131 insertions(+), 38 deletions(-)

(limited to 'src')

diff --git a/src/Text/Pandoc/Readers/Docx/Parse.hs b/src/Text/Pandoc/Readers/Docx/Parse.hs
index b9021ec08..7b9779105 100644
--- a/src/Text/Pandoc/Readers/Docx/Parse.hs
+++ b/src/Text/Pandoc/Readers/Docx/Parse.hs
@@ -65,7 +65,7 @@ import Control.Monad.State
 import Control.Applicative ((<|>))
 import qualified Data.Map as M
 import Control.Monad.Except
-import Text.Pandoc.Shared (safeRead)
+import Text.Pandoc.Shared (safeRead, filteredFilesFromArchive)
 import Text.TeXMath.Readers.OMML (readOMML)
 import Text.Pandoc.Readers.Docx.Fonts (getUnicode, Font(..))
 import Text.TeXMath (Exp)
@@ -86,7 +86,6 @@ data ReaderEnv = ReaderEnv { envNotes         :: Notes
 
 data ReaderState = ReaderState { stateWarnings :: [String] }
                  deriving Show
-                                                  
 
 data DocxError = DocxError | WrongElem
                deriving Show
@@ -276,7 +275,7 @@ archiveToDocxWithWarnings archive = do
       comments  = archiveToComments archive
       numbering = archiveToNumbering archive
       rels      = archiveToRelationships archive
-      media     = archiveToMedia archive
+      media     = filteredFilesFromArchive archive filePathIsMedia
       (styles, parstyles) = archiveToStyles archive
       rEnv =
         ReaderEnv notes comments numbering rels media Nothing styles parstyles InDocument
@@ -402,7 +401,6 @@ archiveToComments zf =
     case cmts of
       Just c -> Comments cmts_namespaces c
       Nothing -> Comments cmts_namespaces M.empty
-               
 
 filePathToRelType :: FilePath -> Maybe DocumentLocation
 filePathToRelType "word/_rels/document.xml.rels" = Just InDocument
@@ -424,7 +422,7 @@ filePathToRelationships ar fp | Just relType <- filePathToRelType fp
                               , Just relElems <- (parseXMLDoc . UTF8.toStringLazy . fromEntry) entry =
   mapMaybe (relElemToRelationship relType) $ elChildren relElems
 filePathToRelationships _ _ = []
-                               
+
 archiveToRelationships :: Archive -> [Relationship]
 archiveToRelationships archive =
   concatMap (filePathToRelationships archive) $ filesInArchive archive
@@ -435,16 +433,6 @@ filePathIsMedia fp =
   in
    (dir == "word/media/")
 
-getMediaPair :: Archive -> FilePath -> Maybe (FilePath, B.ByteString)
-getMediaPair zf fp =
-  case findEntryByPath fp zf of
-    Just e -> Just (fp, fromEntry e)
-    Nothing -> Nothing
-
-archiveToMedia :: Archive -> Media
-archiveToMedia zf =
-  mapMaybe (getMediaPair zf) (filter filePathIsMedia (filesInArchive zf))
-
 lookupLevel :: String -> String -> Numbering -> Maybe Level
 lookupLevel numId ilvl (Numbering _ numbs absNumbs) = do
   absNumId <- lookup numId $ map (\(Numb nid absnumid) -> (nid, absnumid)) numbs
@@ -741,7 +729,7 @@ elemToCommentStart ns element
   , Just cmtDate <- findAttr (elemName ns "w" "date") element = do
       bps <- mapD (elemToBodyPart ns) (elChildren element)
       return $ CommentStart cmtId cmtAuthor cmtDate bps
-elemToCommentStart _ _ = throwError WrongElem      
+elemToCommentStart _ _ = throwError WrongElem
 
 lookupFootnote :: String -> Notes -> Maybe Element
 lookupFootnote s (Notes _ fns _) = fns >>= (M.lookup s)
diff --git a/src/Text/Pandoc/Readers/Odt.hs b/src/Text/Pandoc/Readers/Odt.hs
index 68e89263c..046fb4d6d 100644
--- a/src/Text/Pandoc/Readers/Odt.hs
+++ b/src/Text/Pandoc/Readers/Odt.hs
@@ -37,6 +37,8 @@ import qualified Text.XML.Light                        as XML
 
 import qualified Data.ByteString.Lazy                  as B
 
+import           System.FilePath
+
 import           Text.Pandoc.Definition
 import           Text.Pandoc.Error
 import           Text.Pandoc.Options
@@ -48,39 +50,49 @@ import           Text.Pandoc.Readers.Odt.StyleReader
 
 import           Text.Pandoc.Readers.Odt.Generic.XMLConverter
 import           Text.Pandoc.Readers.Odt.Generic.Fallible
+import           Text.Pandoc.Shared (filteredFilesFromArchive)
 
 --
 readOdt :: ReaderOptions
         -> B.ByteString
         -> Either PandocError (Pandoc, MediaBag)
-readOdt _ bytes = case bytesToOdt bytes of
-                    Right pandoc -> Right (pandoc , mempty)
-                    Left  err    -> Left err
+readOdt _ bytes = bytesToOdt bytes-- of
+--                    Right (pandoc, mediaBag) -> Right (pandoc , mediaBag)
+--                    Left  err                -> Left err
 
 --
-bytesToOdt :: B.ByteString -> Either PandocError Pandoc
+bytesToOdt :: B.ByteString -> Either PandocError (Pandoc, MediaBag)
 bytesToOdt bytes = case toArchiveOrFail bytes of
   Right archive -> archiveToOdt archive
   Left _        -> Left $ ParseFailure "Couldn't parse odt file."
 
 --
-archiveToOdt :: Archive -> Either PandocError Pandoc
+archiveToOdt :: Archive -> Either PandocError (Pandoc, MediaBag)
 archiveToOdt archive
-  | Just contentEntry <- findEntryByPath "content.xml" archive
-  , Just stylesEntry  <- findEntryByPath "styles.xml"  archive
-  , Just contentElem  <- entryToXmlElem contentEntry
-  , Just stylesElem   <- entryToXmlElem stylesEntry
-  , Right styles      <- chooseMax (readStylesAt stylesElem )
-                                   (readStylesAt contentElem)
-  , startState        <- readerState styles
-  , Right pandoc      <- runConverter' read_body
-                                       startState
-                                       contentElem
-  = Right pandoc
+  | Just contentEntry      <- findEntryByPath "content.xml" archive
+  , Just stylesEntry       <- findEntryByPath "styles.xml"  archive
+  , Just contentElem       <- entryToXmlElem contentEntry
+  , Just stylesElem        <- entryToXmlElem stylesEntry
+  , Right styles           <- chooseMax (readStylesAt stylesElem )
+                                        (readStylesAt contentElem)
+  , media                  <- filteredFilesFromArchive archive filePathIsOdtMedia
+  , startState             <- readerState styles media
+  , Right pandocWithMedia  <- runConverter' read_body
+                                            startState
+                                            contentElem
+
+  = Right pandocWithMedia
 
   | otherwise
     -- Not very detailed, but I don't think more information would be helpful
   = Left $ ParseFailure "Couldn't parse odt file."
+    where
+      filePathIsOdtMedia :: FilePath -> Bool
+      filePathIsOdtMedia fp =
+        let (dir, _) = splitFileName fp
+        in
+         (dir == "Pictures/")
+
 
 --
 entryToXmlElem :: Entry -> Maybe XML.Element
diff --git a/src/Text/Pandoc/Readers/Odt/ContentReader.hs b/src/Text/Pandoc/Readers/Odt/ContentReader.hs
index 8c475eefc..d61707976 100644
--- a/src/Text/Pandoc/Readers/Odt/ContentReader.hs
+++ b/src/Text/Pandoc/Readers/Odt/ContentReader.hs
@@ -42,6 +42,7 @@ module Text.Pandoc.Readers.Odt.ContentReader
 import           Control.Arrow
 import           Control.Applicative    hiding ( liftA, liftA2, liftA3 )
 
+import qualified Data.ByteString.Lazy   as B
 import qualified Data.Map               as M
 import           Data.List                     ( find )
 import           Data.Maybe
@@ -50,6 +51,7 @@ import qualified Text.XML.Light         as XML
 
 import           Text.Pandoc.Definition
 import           Text.Pandoc.Builder
+import           Text.Pandoc.MediaBag (insertMedia, MediaBag)
 import           Text.Pandoc.Shared
 
 import           Text.Pandoc.Readers.Odt.Base
@@ -68,6 +70,7 @@ import qualified Data.Set as Set
 --------------------------------------------------------------------------------
 
 type Anchor = String
+type Media = [(FilePath, B.ByteString)]
 
 data ReaderState
    = ReaderState { -- | A collection of styles read somewhere else.
@@ -87,14 +90,17 @@ data ReaderState
                    -- | A map from internal anchor names to "pretty" ones.
                    -- The mapping is a purely cosmetic one.
                  , bookmarkAnchors  :: M.Map Anchor Anchor
-
+                   -- | A map of files / binary data from the archive
+                 , envMedia         :: Media
+                   -- | Hold binary resources used in the document
+                 , odtMediaBag      :: MediaBag
 --               , sequences
 --               , trackedChangeIDs
                  }
   deriving ( Show )
 
-readerState :: Styles -> ReaderState
-readerState styles = ReaderState styles [] 0 Nothing M.empty
+readerState :: Styles -> Media -> ReaderState
+readerState styles media = ReaderState styles [] 0 Nothing M.empty media mempty
 
 --
 pushStyle'  :: Style -> ReaderState -> ReaderState
@@ -134,6 +140,16 @@ putPrettyAnchor ugly pretty state@ReaderState{..}
 usedAnchors :: ReaderState -> [Anchor]
 usedAnchors ReaderState{..} = M.elems bookmarkAnchors
 
+getMediaBag :: ReaderState -> MediaBag
+getMediaBag ReaderState{..} = odtMediaBag
+
+getMediaEnv :: ReaderState -> Media
+getMediaEnv ReaderState{..} = envMedia
+
+insertMedia' :: (FilePath, B.ByteString) -> ReaderState ->  ReaderState
+insertMedia' (fp, bs) state@ReaderState{..}
+  = state { odtMediaBag = insertMedia fp Nothing bs odtMediaBag }
+
 --------------------------------------------------------------------------------
 -- Reader type and associated tools
 --------------------------------------------------------------------------------
@@ -190,6 +206,22 @@ popStyle =     keepingTheValue (
 getCurrentListLevel :: OdtReaderSafe _x ListLevel
 getCurrentListLevel = getExtraState >>^ currentListLevel
 
+--
+updateMediaWithResource :: OdtReaderSafe (FilePath, B.ByteString) (FilePath, B.ByteString)
+updateMediaWithResource = keepingTheValue (
+                 (keepingTheValue getExtraState
+                  >>% insertMedia'
+                  )
+                 >>> setExtraState
+               )
+           >>^ fst
+
+lookupResource :: OdtReaderSafe String (FilePath, B.ByteString)
+lookupResource = proc target -> do
+    state <- getExtraState -< ()
+    case lookup target (getMediaEnv state) of
+      Just bs -> returnV (target, bs) -<< ()
+      Nothing -> returnV ("", B.empty) -< ()
 
 type AnchorPrefix = String
 
@@ -559,6 +591,7 @@ read_paragraph    = matchingElement NsText "p"
                                         , read_reference_start
                                         , read_bookmark_ref
                                         , read_reference_ref
+                                        , read_frame
                                         ] read_plain_text
 
 
@@ -583,6 +616,7 @@ read_header       = matchingElement NsText "h"
                                   , read_reference_start
                                   , read_bookmark_ref
                                   , read_reference_ref
+                                  , read_frame
                                   ] read_plain_text
               ) -< blocks
   anchor   <- getHeaderAnchor -< children
@@ -687,6 +721,46 @@ read_table_cell    = matchingElement NsTable "table-cell"
                      $ matchChildContent' [ read_paragraph
                                           ]
 
+----------------------
+-- Images
+----------------------
+
+--
+read_frame  :: InlineMatcher
+read_frame   = matchingElement NsDraw "frame"
+               $ proc blocks -> do
+                  w          <- ( findAttr' NsSVG "width" ) -< ()
+                  h          <- ( findAttr' NsSVG "height" ) -< ()
+                  attr       <- arr (uncurry image_attributes) -< (w, h)
+                  titleNodes <- ( matchChildContent' [ read_frame_title ] ) -< blocks
+                  title      <- arr inlineListToIdentifier -< (toList titleNodes)
+                  src        <-  matchChildContent' [ read_image_src ] -< blocks
+                  resource   <- lookupResource -< src
+                  _          <- updateMediaWithResource -< resource
+                  arr (uncurry4 imageWith ) -< (attr, src, title, mempty)
+
+image_attributes :: Maybe String -> Maybe String -> Attr
+image_attributes x y =
+  ( "", [], (dim "width" x) ++ (dim "height" y))
+  where
+    dim _ (Just "")   = []
+    dim name (Just v) = [(name, v)]
+    dim _ Nothing     = []
+
+read_image_src :: (Namespace, ElementName, OdtReader Anchor Anchor)
+read_image_src = matchingElement NsDraw "image"
+                   $ proc _ -> do
+                       imgSrc <- findAttr NsXLink "href" -< ()
+                       case imgSrc of
+                          Right src -> returnV src -<< ()
+                          Left _    -> returnV "" -< ()
+
+read_frame_title :: InlineMatcher
+read_frame_title = matchingElement NsSVG "title"
+                   $ (matchChildContent [] read_plain_text)
+
+
+
 ----------------------
 -- Internal links
 ----------------------
@@ -783,8 +857,11 @@ read_text = matchChildContent' [ read_header
                                ]
             >>^ doc
 
-read_body :: OdtReader _x Pandoc
+read_body :: OdtReader _x (Pandoc, MediaBag)
 read_body = executeIn NsOffice "body"
           $ executeIn NsOffice "text"
-          $ liftAsSuccess read_text
-
+          $ liftAsSuccess
+          $ proc inlines -> do
+             txt   <- read_text     -< inlines
+             state <- getExtraState -< ()
+             returnA                -< (txt, getMediaBag state)
diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs
index 04752a194..7e8cd571f 100644
--- a/src/Text/Pandoc/Shared.hs
+++ b/src/Text/Pandoc/Shared.hs
@@ -67,6 +67,7 @@ module Text.Pandoc.Shared (
                      Element (..),
                      hierarchicalize,
                      uniqueIdent,
+                     inlineListToIdentifier,
                      isHeaderBlock,
                      headerShift,
                      isTightList,
@@ -84,6 +85,7 @@ module Text.Pandoc.Shared (
                      fetchItem',
                      openURL,
                      collapseFilePath,
+                     filteredFilesFromArchive,
                      -- * Error handling
                      err,
                      warn,
@@ -110,6 +112,7 @@ import System.Exit (exitWith, ExitCode(..))
 import Data.Char ( toLower, isLower, isUpper, isAlpha,
                    isLetter, isDigit, isSpace )
 import Data.List ( find, stripPrefix, intercalate )
+import Data.Maybe (mapMaybe)
 import Data.Version ( showVersion )
 import qualified Data.Map as M
 import Network.URI ( escapeURIString, nonStrictRelativeTo,
@@ -1028,6 +1031,19 @@ collapseFilePath = Posix.joinPath . reverse . foldl go [] . splitDirectories
     isSingleton _ = Nothing
     checkPathSeperator = fmap isPathSeparator . isSingleton
 
+--
+-- File selection from the archive
+--
+filteredFilesFromArchive :: Archive -> (FilePath -> Bool) -> [(FilePath, BL.ByteString)]
+filteredFilesFromArchive zf f =
+  mapMaybe (fileAndBinary zf) (filter f (filesInArchive zf))
+  where
+    fileAndBinary :: Archive -> FilePath -> Maybe (FilePath, BL.ByteString)
+    fileAndBinary a fp =
+      case findEntryByPath fp a of
+        Just e -> Just (fp, fromEntry e)
+        Nothing -> Nothing
+
 ---
 --- Squash blocks into inlines
 ---
-- 
cgit v1.2.3


From a02f276ff125eb9bede33524371cf8c7b660bb40 Mon Sep 17 00:00:00 2001
From: Hubert Plociniczak <hubert.plociniczak@gmail.com>
Date: Mon, 17 Oct 2016 16:35:13 +0200
Subject: Infer caption from the text following the img

Frame can contain other frames with the text boxes.
This is something that has not been considered before
and meant that the whole construction of images was
broken in those cases. Also the captions were fixed/ignored.
---
 src/Text/Pandoc/Readers/Odt/ContentReader.hs | 67 +++++++++++++++++++---------
 tests/Tests/Readers/Odt.hs                   |  6 ++-
 tests/odt/native/image.native                |  1 +
 tests/odt/native/imageIndex.native           |  1 +
 tests/odt/native/imageWithCaption.native     |  1 +
 5 files changed, 54 insertions(+), 22 deletions(-)
 create mode 100644 tests/odt/native/image.native
 create mode 100644 tests/odt/native/imageIndex.native
 create mode 100644 tests/odt/native/imageWithCaption.native

(limited to 'src')

diff --git a/src/Text/Pandoc/Readers/Odt/ContentReader.hs b/src/Text/Pandoc/Readers/Odt/ContentReader.hs
index d61707976..166fce681 100644
--- a/src/Text/Pandoc/Readers/Odt/ContentReader.hs
+++ b/src/Text/Pandoc/Readers/Odt/ContentReader.hs
@@ -543,6 +543,10 @@ read_plain_text =  fst ^&&& read_plain_text' >>% recover
     extractText (XML.Text cData) = succeedWith (XML.cdData cData)
     extractText         _        = failEmpty
 
+read_text_seq :: InlineMatcher
+read_text_seq  = matchingElement NsText "sequence"
+                 $ matchChildContent [] read_plain_text
+
 
 -- specifically. I honor that, although the current implementation of '(<>)'
 -- for 'Inlines' in "Text.Pandoc.Builder" will collaps them agein.
@@ -591,7 +595,8 @@ read_paragraph    = matchingElement NsText "p"
                                         , read_reference_start
                                         , read_bookmark_ref
                                         , read_reference_ref
-                                        , read_frame
+                                        , read_maybe_nested_img_frame
+                                        , read_text_seq
                                         ] read_plain_text
 
 
@@ -616,7 +621,7 @@ read_header       = matchingElement NsText "h"
                                   , read_reference_start
                                   , read_bookmark_ref
                                   , read_reference_ref
-                                  , read_frame
+                                  , read_maybe_nested_img_frame
                                   ] read_plain_text
               ) -< blocks
   anchor   <- getHeaderAnchor -< children
@@ -726,18 +731,26 @@ read_table_cell    = matchingElement NsTable "table-cell"
 ----------------------
 
 --
-read_frame  :: InlineMatcher
-read_frame   = matchingElement NsDraw "frame"
-               $ proc blocks -> do
-                  w          <- ( findAttr' NsSVG "width" ) -< ()
-                  h          <- ( findAttr' NsSVG "height" ) -< ()
-                  attr       <- arr (uncurry image_attributes) -< (w, h)
-                  titleNodes <- ( matchChildContent' [ read_frame_title ] ) -< blocks
-                  title      <- arr inlineListToIdentifier -< (toList titleNodes)
-                  src        <-  matchChildContent' [ read_image_src ] -< blocks
-                  resource   <- lookupResource -< src
-                  _          <- updateMediaWithResource -< resource
-                  arr (uncurry4 imageWith ) -< (attr, src, title, mempty)
+read_maybe_nested_img_frame  :: InlineMatcher
+read_maybe_nested_img_frame   = matchingElement NsDraw "frame"
+                                $ proc blocks -> do
+                                   img <- (findChild' NsDraw "image") -< ()
+                                   case img of
+                                     Just _  ->  read_frame                                 -< blocks
+                                     Nothing ->  matchChildContent' [ read_frame_text_box ] -< blocks
+
+read_frame :: OdtReaderSafe Inlines Inlines
+read_frame =
+  proc blocks -> do
+   w          <- ( findAttr' NsSVG "width" )                 -< ()
+   h          <- ( findAttr' NsSVG "height" )                -< ()
+   titleNodes <- ( matchChildContent' [ read_frame_title ] ) -< blocks
+   src        <-  matchChildContent' [ read_image_src ]      -< blocks
+   resource   <- lookupResource                              -< src
+   _          <- updateMediaWithResource                     -< resource
+   alt        <- (matchChildContent [] read_plain_text)      -< blocks
+   arr (uncurry4 imageWith ) -<
+                (image_attributes w h, src, inlineListToIdentifier (toList titleNodes), alt)
 
 image_attributes :: Maybe String -> Maybe String -> Attr
 image_attributes x y =
@@ -749,17 +762,31 @@ image_attributes x y =
 
 read_image_src :: (Namespace, ElementName, OdtReader Anchor Anchor)
 read_image_src = matchingElement NsDraw "image"
-                   $ proc _ -> do
-                       imgSrc <- findAttr NsXLink "href" -< ()
-                       case imgSrc of
-                          Right src -> returnV src -<< ()
-                          Left _    -> returnV "" -< ()
+                 $ proc _ -> do
+                    imgSrc <- findAttr NsXLink "href" -< ()
+                    case imgSrc of
+                      Right src -> returnV src -<< ()
+                      Left _    -> returnV ""  -< ()
 
 read_frame_title :: InlineMatcher
 read_frame_title = matchingElement NsSVG "title"
                    $ (matchChildContent [] read_plain_text)
 
-
+read_frame_text_box :: InlineMatcher
+read_frame_text_box = matchingElement NsDraw "text-box"
+                      $ proc blocks -> do
+                         paragraphs <- (matchChildContent' [ read_paragraph ]) -< blocks
+                         case toList paragraphs of
+                           (p : [])  ->                 -- require only a single paragraph
+                             arr read_img_with_caption -< p
+                           _         ->
+                             arr fromList              -< []
+
+read_img_with_caption :: Block -> Inlines
+read_img_with_caption (Para ((Image attr _ target) : txt)) =
+  singleton (Image attr txt target)                     -- override caption with the text that follows
+read_img_with_caption _ =
+  fromList []
 
 ----------------------
 -- Internal links
diff --git a/tests/Tests/Readers/Odt.hs b/tests/Tests/Readers/Odt.hs
index cf30b8398..74796d899 100644
--- a/tests/Tests/Readers/Odt.hs
+++ b/tests/Tests/Readers/Odt.hs
@@ -141,7 +141,6 @@ namesOfTestsComparingToMarkdown  = [ "bold"
                                    , "footnote"
                                    , "headers"
 --                                 , "horizontalRule"
---                                 , "image"
                                    , "italic"
 --                                 , "listBlocks"
                                    , "paragraph"
@@ -152,6 +151,9 @@ namesOfTestsComparingToMarkdown  = [ "bold"
 
 namesOfTestsComparingToNative  :: [ String ]
 namesOfTestsComparingToNative   = [ "blockquote"
+                                  , "image"
+                                  , "imageIndex"
+                                  , "imageWithCaption"
                                   , "orderedListMixed"
                                   , "orderedListRoman"
                                   , "orderedListSimple"
@@ -162,4 +164,4 @@ namesOfTestsComparingToNative   = [ "blockquote"
 --                                , "table"
                                   , "unicode"
                                   , "unorderedList"
-                                  ]
\ No newline at end of file
+                                  ]
diff --git a/tests/odt/native/image.native b/tests/odt/native/image.native
new file mode 100644
index 000000000..667442539
--- /dev/null
+++ b/tests/odt/native/image.native
@@ -0,0 +1 @@
+[Para [Image ("",[],[("width","5.292cm"),("height","5.292cm")]) [] ("Pictures/10000000000000FA000000FAD6A15225.jpg","")]]
diff --git a/tests/odt/native/imageIndex.native b/tests/odt/native/imageIndex.native
new file mode 100644
index 000000000..75c6e4135
--- /dev/null
+++ b/tests/odt/native/imageIndex.native
@@ -0,0 +1 @@
+[Para [Image ("",[],[("width","5.292cm"),("height","5.292cm")]) [Str "Abbildung",Space,Str "1:",Space,Str "Image",Space,Str "caption"] ("Pictures/10000000000000FA000000FAD6A15225.jpg","")]]
diff --git a/tests/odt/native/imageWithCaption.native b/tests/odt/native/imageWithCaption.native
new file mode 100644
index 000000000..75c6e4135
--- /dev/null
+++ b/tests/odt/native/imageWithCaption.native
@@ -0,0 +1 @@
+[Para [Image ("",[],[("width","5.292cm"),("height","5.292cm")]) [Str "Abbildung",Space,Str "1:",Space,Str "Image",Space,Str "caption"] ("Pictures/10000000000000FA000000FAD6A15225.jpg","")]]
-- 
cgit v1.2.3


From 7234321e8f5e77422e2c1be7ac3264d302083767 Mon Sep 17 00:00:00 2001
From: Hubert Plociniczak <hubert.plociniczak@gmail.com>
Date: Mon, 17 Oct 2016 16:50:03 +0200
Subject: Minor refactoring

---
 src/Text/Pandoc/Readers/Odt/ContentReader.hs | 16 ++++++----------
 1 file changed, 6 insertions(+), 10 deletions(-)

(limited to 'src')

diff --git a/src/Text/Pandoc/Readers/Odt/ContentReader.hs b/src/Text/Pandoc/Readers/Odt/ContentReader.hs
index 166fce681..1aaff62e5 100644
--- a/src/Text/Pandoc/Readers/Odt/ContentReader.hs
+++ b/src/Text/Pandoc/Readers/Odt/ContentReader.hs
@@ -776,17 +776,13 @@ read_frame_text_box :: InlineMatcher
 read_frame_text_box = matchingElement NsDraw "text-box"
                       $ proc blocks -> do
                          paragraphs <- (matchChildContent' [ read_paragraph ]) -< blocks
-                         case toList paragraphs of
-                           (p : [])  ->                 -- require only a single paragraph
-                             arr read_img_with_caption -< p
-                           _         ->
-                             arr fromList              -< []
-
-read_img_with_caption :: Block -> Inlines
-read_img_with_caption (Para ((Image attr _ target) : txt)) =
-  singleton (Image attr txt target)                     -- override caption with the text that follows
+                         arr read_img_with_caption                             -< toList paragraphs
+
+read_img_with_caption :: [Block] -> Inlines
+read_img_with_caption ((Para ((Image attr _ target) : txt)) : _) =
+  singleton (Image attr txt target)             -- override caption with the text that follows
 read_img_with_caption _ =
-  fromList []
+  mempty
 
 ----------------------
 -- Internal links
-- 
cgit v1.2.3


From 4417e33ea9d49a2001091adb4d2b19ebdefe5795 Mon Sep 17 00:00:00 2001
From: Hubert Plociniczak <hubert.plociniczak@gmail.com>
Date: Mon, 17 Oct 2016 16:58:53 +0200
Subject: Use bind function instead of pattern matching

---
 src/Text/Pandoc/Shared.hs | 5 +----
 1 file changed, 1 insertion(+), 4 deletions(-)

(limited to 'src')

diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs
index 7e8cd571f..0760b49f8 100644
--- a/src/Text/Pandoc/Shared.hs
+++ b/src/Text/Pandoc/Shared.hs
@@ -1039,10 +1039,7 @@ filteredFilesFromArchive zf f =
   mapMaybe (fileAndBinary zf) (filter f (filesInArchive zf))
   where
     fileAndBinary :: Archive -> FilePath -> Maybe (FilePath, BL.ByteString)
-    fileAndBinary a fp =
-      case findEntryByPath fp a of
-        Just e -> Just (fp, fromEntry e)
-        Nothing -> Nothing
+    fileAndBinary a fp = findEntryByPath fp a >>= \e -> Just (fp, fromEntry e)
 
 ---
 --- Squash blocks into inlines
-- 
cgit v1.2.3