EPUB Reader: Fixed regressions in image extraction

Before the images were relative to the position of the package file. The
collapse function changed this so that they were then absolute in the
archive but the fetchImages function wasn't updated to recognise this.
This commit is contained in:
Matthew Pickering 2014-08-08 22:28:08 +01:00
parent 8c551f6f43
commit 40ae8efddc

View file

@ -62,7 +62,7 @@ archiveToEPUB (setEPUBOptions -> os) archive = do
foldM' (\a b -> ((a <>) . bottomUp (prependHash escapedSpine))
`liftM` parseSpineElem root b) mempty spine
let ast = coverDoc <> (Pandoc meta bs)
let mediaBag = fetchImages (M.elems items) root archive ast
let mediaBag = fetchImages (M.elems items) archive ast
return $ (ast, mediaBag)
where
parseSpineElem :: MonadError String m => FilePath -> (FilePath, MIME) -> m Pandoc
@ -89,19 +89,19 @@ setEPUBOptions os = os''
os' = os {readerExtensions = foldr S.insert rs [Ext_epub_html_exts]}
os'' = os' {readerParseRaw = True}
-- paths should be absolute when this function is called
-- renameImages should do this
fetchImages :: [(FilePath, MIME)]
-> FilePath
-> Archive
-> Pandoc
-> MediaBag
fetchImages mimes root arc (query iq -> links) =
fetchImages mimes arc (query iq -> links) =
foldr (uncurry3 insertMedia) mempty
(mapMaybe getEntry links)
where
getEntry (normalise -> l) =
let mediaPos = normalise (root </> l) in
(l , lookup mediaPos mimes, ) . fromEntry
<$> findEntryByPath mediaPos arc
getEntry link =
(link , lookup link mimes, ) . fromEntry
<$> findEntryByPath link arc
iq :: Inline -> [FilePath]
iq (Image _ (url, _)) = [url]