Introduce DeferredMediaBag.
This is a lazy MediaBag, that will only be evaluated (downloaded/read in) upon demand. Note that we use fetchItem in getDefferedMedia at the moment to read in/download. This means that we don't need to distinguish between URIs and FilePaths. But there is an inefficiency here: `fetchItem` will pull an item out of the mediaBag if it's already there, and then we'll reinsert it. We could separate out `fetchItem` into the function that checks the MediaBag and the underlying downloader/read-inner.
This commit is contained in:
parent
adcd4c5b7b
commit
5814096d79
1 changed files with 24 additions and 0 deletions
|
@ -100,6 +100,7 @@ import Data.Default
|
|||
import System.IO.Error
|
||||
import qualified Data.Map as M
|
||||
import Text.Pandoc.Error
|
||||
import Data.Monoid
|
||||
|
||||
class (Functor m, Applicative m, Monad m, MonadError PandocError m)
|
||||
=> PandocMonad m where
|
||||
|
@ -167,6 +168,29 @@ warningWithPos pos msg = lift $ warning $ msg ++ " " ++ show pos
|
|||
|
||||
--
|
||||
|
||||
newtype DeferredMediaPath = DeferredMediaPath {unDefer :: String}
|
||||
deriving (Show, Eq)
|
||||
|
||||
data DeferredMediaBag = DeferredMediaBag MediaBag [DeferredMediaPath]
|
||||
deriving (Show)
|
||||
|
||||
instance Monoid DeferredMediaBag where
|
||||
mempty = DeferredMediaBag mempty mempty
|
||||
mappend (DeferredMediaBag mb lst) (DeferredMediaBag mb' lst') =
|
||||
DeferredMediaBag (mb <> mb') (lst <> lst')
|
||||
|
||||
getDeferredMedia :: PandocMonad m => DeferredMediaBag -> m MediaBag
|
||||
getDeferredMedia (DeferredMediaBag mb defMedia) = do
|
||||
fetchedMedia <- mapM (\dfp -> fetchItem Nothing (unDefer dfp)) defMedia
|
||||
return $ foldr
|
||||
(\(dfp, (bs, mbMime)) mb' ->
|
||||
MB.insertMedia (unDefer dfp) mbMime (BL.fromStrict bs) mb')
|
||||
mb
|
||||
(zip defMedia fetchedMedia)
|
||||
|
||||
dropDeferredMedia :: DeferredMediaBag -> MediaBag
|
||||
dropDeferredMedia (DeferredMediaBag mb _) = mb
|
||||
|
||||
data CommonState = CommonState { stWarnings :: [String]
|
||||
, stMediaBag :: MediaBag
|
||||
, stInputFiles :: Maybe [FilePath]
|
||||
|
|
Loading…
Add table
Reference in a new issue