aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Readers/Docx
diff options
context:
space:
mode:
authorHubert Plociniczak <hubert.plociniczak@gmail.com>2016-10-12 17:42:30 +0200
committerHubert Plociniczak <hubert.plociniczak@gmail.com>2016-10-12 17:50:35 +0200
commitc924611de526601f64154bef83035f75e8f4c334 (patch)
treef665c276c4683f018e06357b0efe34ff43450c6b /src/Text/Pandoc/Readers/Docx
parentcbeb72d06b4eb3718479eba5257a33a385f642fe (diff)
downloadpandoc-c924611de526601f64154bef83035f75e8f4c334.tar.gz
Basic support for images in ODT documents
Highly influenced by the docx support, refactored some code to avoid DRY.
Diffstat (limited to 'src/Text/Pandoc/Readers/Docx')
-rw-r--r--src/Text/Pandoc/Readers/Docx/Parse.hs20
1 files changed, 4 insertions, 16 deletions
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)