aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Lua/Marshaling/MediaBag.hs
diff options
context:
space:
mode:
authorAlbert Krewinkel <albert@zeitkraut.de>2019-02-15 17:13:04 +0100
committerAlbert Krewinkel <albert@zeitkraut.de>2019-05-29 23:17:12 +0200
commit3097ee100ed260a5c2cea7df5bf80c989687df44 (patch)
treee42fc606fb96b93f09422203470013b9b825832c /src/Text/Pandoc/Lua/Marshaling/MediaBag.hs
parent8507d98a1534ba4049e4c1ca3671ee41a1f56c70 (diff)
downloadpandoc-3097ee100ed260a5c2cea7df5bf80c989687df44.tar.gz
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`.
Diffstat (limited to 'src/Text/Pandoc/Lua/Marshaling/MediaBag.hs')
-rw-r--r--src/Text/Pandoc/Lua/Marshaling/MediaBag.hs75
1 files changed, 75 insertions, 0 deletions
diff --git a/src/Text/Pandoc/Lua/Marshaling/MediaBag.hs b/src/Text/Pandoc/Lua/Marshaling/MediaBag.hs
new file mode 100644
index 000000000..816843c1d
--- /dev/null
+++ b/src/Text/Pandoc/Lua/Marshaling/MediaBag.hs
@@ -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