pandoc.mediabag module: add items function iterating over mediabag
A new function `pandoc.mediabag.items` was added to Lua module pandoc.mediabag. This allows users to lazily iterate over all media bag items, loading items into Lua one-by-one. Example: for filename, mime_type, content in pandoc.mediabag.items() do -- use media bag item. end This is a convenient alternative to using `mediabag.list` in combination with `mediabag.lookup`.
This commit is contained in:
parent
8507d98a15
commit
3097ee100e
5 changed files with 116 additions and 1 deletions
|
@ -2475,6 +2475,33 @@ Usage:
|
|||
local contents = "Hello, World!"
|
||||
pandoc.mediabag(fp, mt, contents)
|
||||
|
||||
### iter {#mediabag-iter}
|
||||
|
||||
`items ()`
|
||||
|
||||
Returns an iterator triple to be used with Lua's generic `for`
|
||||
statement. The iterator returns the filepath, MIME type, and
|
||||
content of a media bag item on each invocation. Items are
|
||||
processed one-by-one to avoid excessive memory use.
|
||||
|
||||
This function should be used only when full access to all items,
|
||||
including their contents, is required. For all other cases,
|
||||
[`list`](#mediabag-list) should be preferred.
|
||||
|
||||
Returns:
|
||||
|
||||
- The iterator function; must be called with the iterator state
|
||||
and the current iterator value.
|
||||
- Iterator state – an opaque value to be passed to the iterator
|
||||
function.
|
||||
- Initial iterator value.
|
||||
|
||||
Usage:
|
||||
|
||||
for fp, mt, contents in pandoc.mediabag.items() do
|
||||
-- print(fp, mt, contents)
|
||||
end
|
||||
|
||||
### list {#mediabag-list}
|
||||
|
||||
`list ()`
|
||||
|
|
|
@ -591,6 +591,7 @@ library
|
|||
Text.Pandoc.Lua.Marshaling.AST,
|
||||
Text.Pandoc.Lua.Marshaling.AnyValue,
|
||||
Text.Pandoc.Lua.Marshaling.CommonState,
|
||||
Text.Pandoc.Lua.Marshaling.MediaBag,
|
||||
Text.Pandoc.Lua.Marshaling.ReaderOptions,
|
||||
Text.Pandoc.Lua.Marshaling.Version,
|
||||
Text.Pandoc.Lua.Module.MediaBag,
|
||||
|
|
75
src/Text/Pandoc/Lua/Marshaling/MediaBag.hs
Normal file
75
src/Text/Pandoc/Lua/Marshaling/MediaBag.hs
Normal file
|
@ -0,0 +1,75 @@
|
|||
{-# LANGUAGE NoImplicitPrelude #-}
|
||||
{- |
|
||||
Module : Text.Pandoc.Lua.Marshaling.MediaBag
|
||||
Copyright : © 2012-2019 John MacFarlane
|
||||
© 2017-2019 Albert Krewinkel
|
||||
License : GNU GPL, version 2 or above
|
||||
Maintainer : Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
|
||||
Stability : alpha
|
||||
|
||||
Instances to marshal (push) and unmarshal (peek) media data.
|
||||
-}
|
||||
module Text.Pandoc.Lua.Marshaling.MediaBag (pushIterator) where
|
||||
|
||||
import Prelude
|
||||
import Foreign.Ptr (Ptr)
|
||||
import Foreign.StablePtr (StablePtr, deRefStablePtr, newStablePtr)
|
||||
import Foreign.Lua (Lua, NumResults, Peekable, Pushable, StackIndex)
|
||||
import Foreign.Lua.Types.Peekable (reportValueOnFailure)
|
||||
import Foreign.Lua.Userdata (ensureUserdataMetatable, pushAnyWithMetatable,
|
||||
toAnyWithName)
|
||||
import Text.Pandoc.MediaBag (MediaBag, mediaItems)
|
||||
import Text.Pandoc.MIME (MimeType)
|
||||
import Text.Pandoc.Lua.Marshaling.AnyValue (AnyValue (..))
|
||||
|
||||
import qualified Data.ByteString.Lazy as BL
|
||||
import qualified Foreign.Lua as Lua
|
||||
import qualified Foreign.Storable as Storable
|
||||
|
||||
-- | A list of 'MediaBag' items.
|
||||
newtype MediaItems = MediaItems [(String, MimeType, BL.ByteString)]
|
||||
|
||||
instance Pushable MediaItems where
|
||||
push = pushMediaItems
|
||||
|
||||
instance Peekable MediaItems where
|
||||
peek = peekMediaItems
|
||||
|
||||
-- | Push an iterator triple to be used with Lua's @for@ loop construct.
|
||||
-- Each iterator invokation returns a tripple consisting of an item's
|
||||
-- filename, MIME type, and content.
|
||||
pushIterator :: MediaBag -> Lua NumResults
|
||||
pushIterator mb = do
|
||||
Lua.pushHaskellFunction nextItem
|
||||
Lua.push (MediaItems $ mediaItems mb)
|
||||
Lua.pushnil
|
||||
return 3
|
||||
|
||||
-- | Lua type name for @'MediaItems'@.
|
||||
mediaItemsTypeName :: String
|
||||
mediaItemsTypeName = "pandoc MediaItems"
|
||||
|
||||
-- | Push a @MediaItems@ element to the stack.
|
||||
pushMediaItems :: MediaItems -> Lua ()
|
||||
pushMediaItems xs = pushAnyWithMetatable pushMT xs
|
||||
where
|
||||
pushMT = ensureUserdataMetatable mediaItemsTypeName (return ())
|
||||
|
||||
-- | Retrieve a @MediaItems@ element from the stack.
|
||||
peekMediaItems :: StackIndex -> Lua MediaItems
|
||||
peekMediaItems = reportValueOnFailure mediaItemsTypeName
|
||||
(`toAnyWithName` mediaItemsTypeName)
|
||||
|
||||
-- | Retrieve a list of items from an iterator state, return the first
|
||||
-- item (if present), and advance the state.
|
||||
nextItem :: Ptr (StablePtr MediaItems) -> AnyValue -> Lua NumResults
|
||||
nextItem ptr _ = do
|
||||
(MediaItems items) <- Lua.liftIO $ deRefStablePtr =<< Storable.peek ptr
|
||||
case items of
|
||||
[] -> 2 <$ (Lua.pushnil *> Lua.pushnil)
|
||||
(key, mt, content):xs -> do
|
||||
Lua.liftIO $ Storable.poke ptr =<< newStablePtr (MediaItems xs)
|
||||
Lua.push key
|
||||
Lua.push mt
|
||||
Lua.push content
|
||||
return 3
|
|
@ -20,6 +20,7 @@ import Foreign.Lua (Lua, NumResults, Optional, liftIO)
|
|||
import Text.Pandoc.Class (CommonState (..), fetchItem, putCommonState,
|
||||
runIOorExplode, setMediaBag)
|
||||
import Text.Pandoc.Lua.Marshaling ()
|
||||
import Text.Pandoc.Lua.Marshaling.MediaBag (pushIterator)
|
||||
import Text.Pandoc.Lua.Util (addFunction)
|
||||
import Text.Pandoc.MIME (MimeType)
|
||||
|
||||
|
@ -34,6 +35,7 @@ pushModule :: Lua NumResults
|
|||
pushModule = do
|
||||
Lua.newtable
|
||||
addFunction "insert" insertMediaFn
|
||||
addFunction "items" items
|
||||
addFunction "lookup" lookupMediaFn
|
||||
addFunction "list" mediaDirectoryFn
|
||||
addFunction "fetch" fetch
|
||||
|
@ -66,9 +68,13 @@ insertMediaFn fp optionalMime contents = do
|
|||
modifyCommonState $ \st ->
|
||||
let mb = MB.insertMedia fp (Lua.fromOptional optionalMime) contents
|
||||
(stMediaBag st)
|
||||
in st { stMediaBag = mb}
|
||||
in st { stMediaBag = mb }
|
||||
return 0
|
||||
|
||||
-- | Returns iterator values to be used with a Lua @for@ loop.
|
||||
items :: Lua NumResults
|
||||
items = stMediaBag <$> getCommonState >>= pushIterator
|
||||
|
||||
lookupMediaFn :: FilePath
|
||||
-> Lua NumResults
|
||||
lookupMediaFn fp = do
|
||||
|
|
|
@ -19,6 +19,7 @@ module Text.Pandoc.MediaBag (
|
|||
lookupMedia,
|
||||
insertMedia,
|
||||
mediaDirectory,
|
||||
mediaItems
|
||||
) where
|
||||
import Prelude
|
||||
import qualified Data.ByteString.Lazy as BL
|
||||
|
@ -66,3 +67,8 @@ mediaDirectory :: MediaBag -> [(String, MimeType, Int)]
|
|||
mediaDirectory (MediaBag mediamap) =
|
||||
M.foldrWithKey (\fp (mime,contents) ->
|
||||
((Posix.joinPath fp, mime, fromIntegral $ BL.length contents):)) [] mediamap
|
||||
|
||||
mediaItems :: MediaBag -> [(String, MimeType, BL.ByteString)]
|
||||
mediaItems (MediaBag mediamap) =
|
||||
M.foldrWithKey (\fp (mime,contents) ->
|
||||
((Posix.joinPath fp, mime, contents):)) [] mediamap
|
||||
|
|
Loading…
Add table
Reference in a new issue