parent
5cd1c1001f
commit
f70795dc5e
1 changed files with 18 additions and 21 deletions
|
@ -1,4 +1,3 @@
|
||||||
{-# LANGUAGE PatternGuards #-}
|
|
||||||
{-# LANGUAGE OverloadedStrings #-}
|
{-# LANGUAGE OverloadedStrings #-}
|
||||||
{- |
|
{- |
|
||||||
Module : Text.Pandoc.Reader.Odt
|
Module : Text.Pandoc.Reader.Odt
|
||||||
|
@ -67,29 +66,27 @@ bytesToOdt bytes = case toArchiveOrFail bytes of
|
||||||
|
|
||||||
--
|
--
|
||||||
archiveToOdt :: Archive -> Either PandocError (Pandoc, MediaBag)
|
archiveToOdt :: Archive -> Either PandocError (Pandoc, MediaBag)
|
||||||
archiveToOdt archive
|
archiveToOdt archive = either (Left. PandocParseError) Right $ do
|
||||||
| Just contentEntry <- findEntryByPath "content.xml" archive
|
let onFailure msg Nothing = Left msg
|
||||||
, Just stylesEntry <- findEntryByPath "styles.xml" archive
|
onFailure _ (Just x) = Right x
|
||||||
, Just contentElem <- entryToXmlElem contentEntry
|
contentEntry <- onFailure "Could not find content.xml"
|
||||||
, Just stylesElem <- entryToXmlElem stylesEntry
|
(findEntryByPath "content.xml" archive)
|
||||||
, Right styles <- chooseMax (readStylesAt stylesElem )
|
stylesEntry <- onFailure "Could not find styles.xml"
|
||||||
(readStylesAt contentElem)
|
(findEntryByPath "styles.xml" archive)
|
||||||
, media <- filteredFilesFromArchive archive filePathIsOdtMedia
|
contentElem <- onFailure "Could not find content element"
|
||||||
, startState <- readerState styles media
|
(entryToXmlElem contentEntry)
|
||||||
, Right pandocWithMedia <- runConverter' read_body
|
stylesElem <- onFailure "Could not find styles element"
|
||||||
startState
|
(entryToXmlElem stylesEntry)
|
||||||
contentElem
|
styles <- either (\_ -> Left "Could not read styles") Right
|
||||||
|
(chooseMax (readStylesAt stylesElem ) (readStylesAt contentElem))
|
||||||
= Right pandocWithMedia
|
let filePathIsOdtMedia :: FilePath -> Bool
|
||||||
|
|
||||||
| otherwise
|
|
||||||
-- Not very detailed, but I don't think more information would be helpful
|
|
||||||
= Left $ PandocParseError "Couldn't parse odt file."
|
|
||||||
where
|
|
||||||
filePathIsOdtMedia :: FilePath -> Bool
|
|
||||||
filePathIsOdtMedia fp =
|
filePathIsOdtMedia fp =
|
||||||
let (dir, name) = splitFileName fp
|
let (dir, name) = splitFileName fp
|
||||||
in (dir == "Pictures/") || (dir /= "./" && name == "content.xml")
|
in (dir == "Pictures/") || (dir /= "./" && name == "content.xml")
|
||||||
|
let media = filteredFilesFromArchive archive filePathIsOdtMedia
|
||||||
|
let startState = readerState styles media
|
||||||
|
either (\_ -> Left "Could not convert opendocument") Right
|
||||||
|
(runConverter' read_body startState contentElem)
|
||||||
|
|
||||||
|
|
||||||
--
|
--
|
||||||
|
|
Loading…
Reference in a new issue