pandoc.mediabag module: add function delete

Function `pandoc.mediabag.delete` allows to remove a single item of the given
name from the media bag.
This commit is contained in:
Albert Krewinkel 2019-02-16 13:35:16 +01:00
parent 0a6a11cfab
commit 5a82ecaaa1
No known key found for this signature in database
GPG key ID: 388DC0B21F631124
3 changed files with 28 additions and 1 deletions

View file

@ -2450,6 +2450,18 @@ e.g.:
local mb = require 'pandoc.mediabag'
### delete {#mediabag-delete}
`delete (filepath)`
Removes a single entry from the media bag.
Parameters:
`filepath`:
: filename of the item to be deleted. The media bag will be
left unchanged if no entry with the given filename exists.
### empty {#mediabag-empty}
`empty ()`

View file

@ -34,6 +34,7 @@ import qualified Text.Pandoc.MediaBag as MB
pushModule :: Lua NumResults
pushModule = do
Lua.newtable
addFunction "delete" delete
addFunction "empty" empty
addFunction "insert" insertMediaFn
addFunction "items" items
@ -61,6 +62,11 @@ setCommonState st = do
modifyCommonState :: (CommonState -> CommonState) -> Lua ()
modifyCommonState f = getCommonState >>= setCommonState . f
-- | Delete a single item from the media bag.
delete :: FilePath -> Lua NumResults
delete fp = 0 <$ modifyCommonState
(\st -> st { stMediaBag = MB.deleteMedia fp (stMediaBag st) })
-- | Delete all items from the media bag.
empty :: Lua NumResults
empty = 0 <$ modifyCommonState (\st -> st { stMediaBag = mempty })
@ -86,7 +92,7 @@ lookupMediaFn :: FilePath
lookupMediaFn fp = do
res <- MB.lookupMedia fp . stMediaBag <$> getCommonState
case res of
Nothing -> Lua.pushnil *> return 1
Nothing -> 1 <$ Lua.pushnil
Just (mimeType, contents) -> do
Lua.push mimeType
Lua.push contents

View file

@ -16,6 +16,7 @@ interface for interacting with it.
-}
module Text.Pandoc.MediaBag (
MediaBag,
deleteMedia,
lookupMedia,
insertMedia,
mediaDirectory,
@ -41,6 +42,14 @@ newtype MediaBag = MediaBag (M.Map [String] (MimeType, BL.ByteString))
instance Show MediaBag where
show bag = "MediaBag " ++ show (mediaDirectory bag)
-- | Delete a media item from a 'MediaBag', or do nothing if no item corresponds
-- to the given path.
deleteMedia :: FilePath -- ^ relative path and canonical name of resource
-> MediaBag
-> MediaBag
deleteMedia fp (MediaBag mediamap) =
MediaBag $ M.delete (splitDirectories fp) mediamap
-- | Insert a media item into a 'MediaBag', replacing any existing
-- value with the same name.
insertMedia :: FilePath -- ^ relative path and canonical name of resource