aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Lua/Module/MediaBag.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Lua/Module/MediaBag.hs')
-rw-r--r--src/Text/Pandoc/Lua/Module/MediaBag.hs157
1 files changed, 90 insertions, 67 deletions
diff --git a/src/Text/Pandoc/Lua/Module/MediaBag.hs b/src/Text/Pandoc/Lua/Module/MediaBag.hs
index 3eed50fca..fb055101e 100644
--- a/src/Text/Pandoc/Lua/Module/MediaBag.hs
+++ b/src/Text/Pandoc/Lua/Module/MediaBag.hs
@@ -1,103 +1,126 @@
+{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{- |
Module : Text.Pandoc.Lua.Module.MediaBag
Copyright : Copyright © 2017-2021 Albert Krewinkel
License : GNU GPL, version 2 or above
-
Maintainer : Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
- Stability : alpha
-The lua module @pandoc.mediabag@.
+The Lua module @pandoc.mediabag@.
-}
module Text.Pandoc.Lua.Module.MediaBag
- ( pushModule
+ ( documentedModule
) where
import Prelude hiding (lookup)
-import Control.Monad (zipWithM_)
-import Foreign.Lua (Lua, NumResults, Optional)
+import Data.Maybe (fromMaybe)
+import HsLua ( LuaE, DocumentedFunction, Module (..)
+ , (<#>), (###), (=#>), (=?>), defun, functionResult
+ , optionalParameter , parameter)
import Text.Pandoc.Class.CommonState (CommonState (..))
import Text.Pandoc.Class.PandocMonad (fetchItem, getMediaBag, modifyCommonState,
setMediaBag)
-import Text.Pandoc.Lua.Marshaling ()
-import Text.Pandoc.Lua.Marshaling.MediaBag (pushIterator)
-import Text.Pandoc.Lua.PandocLua (PandocLua (..), liftPandocLua, addFunction)
+import Text.Pandoc.Error (PandocError)
+import Text.Pandoc.Lua.Marshal.List (pushPandocList)
+import Text.Pandoc.Lua.Orphans ()
+import Text.Pandoc.Lua.PandocLua (unPandocLua)
import Text.Pandoc.MIME (MimeType)
import qualified Data.ByteString.Lazy as BL
-import qualified Data.Text as T
-import qualified Foreign.Lua as Lua
+import qualified HsLua as Lua
import qualified Text.Pandoc.MediaBag as MB
--
-- MediaBag submodule
--
-pushModule :: PandocLua NumResults
-pushModule = do
- liftPandocLua Lua.newtable
- addFunction "delete" delete
- addFunction "empty" empty
- addFunction "insert" insert
- addFunction "items" items
- addFunction "lookup" lookup
- addFunction "list" list
- addFunction "fetch" fetch
- return 1
+documentedModule :: Module PandocError
+documentedModule = Module
+ { moduleName = "pandoc.mediabag"
+ , moduleDescription = "mediabag access"
+ , moduleFields = []
+ , moduleFunctions =
+ [ delete
+ , empty
+ , fetch
+ , insert
+ , items
+ , list
+ , lookup
+ ]
+ , moduleOperations = []
+ }
-- | Delete a single item from the media bag.
-delete :: FilePath -> PandocLua NumResults
-delete fp = 0 <$ modifyCommonState
- (\st -> st { stMediaBag = MB.deleteMedia fp (stMediaBag st) })
+delete :: DocumentedFunction PandocError
+delete = defun "delete"
+ ### (\fp -> unPandocLua $ modifyCommonState
+ (\st -> st { stMediaBag = MB.deleteMedia fp (stMediaBag st) }))
+ <#> parameter Lua.peekString "string" "filepath" "filename of item to delete"
+ =#> []
+
-- | Delete all items from the media bag.
-empty :: PandocLua NumResults
-empty = 0 <$ modifyCommonState (\st -> st { stMediaBag = mempty })
+empty :: DocumentedFunction PandocError
+empty = defun "empty"
+ ### unPandocLua (modifyCommonState (\st -> st { stMediaBag = mempty }))
+ =#> []
-- | Insert a new item into the media bag.
-insert :: FilePath
- -> Optional MimeType
- -> BL.ByteString
- -> PandocLua NumResults
-insert fp optionalMime contents = do
- mb <- getMediaBag
- setMediaBag $ MB.insertMedia fp (Lua.fromOptional optionalMime) contents mb
- return (Lua.NumResults 0)
+insert :: DocumentedFunction PandocError
+insert = defun "insert"
+ ### (\fp mmime contents -> unPandocLua $ do
+ mb <- getMediaBag
+ setMediaBag $ MB.insertMedia fp mmime contents mb
+ return (Lua.NumResults 0))
+ <#> parameter Lua.peekString "string" "filepath" "item file path"
+ <#> optionalParameter Lua.peekText "string" "mimetype" "the item's MIME type"
+ <#> parameter Lua.peekLazyByteString "string" "contents" "binary contents"
+ =?> "Nothing"
-- | Returns iterator values to be used with a Lua @for@ loop.
-items :: PandocLua NumResults
-items = getMediaBag >>= liftPandocLua . pushIterator
+items :: DocumentedFunction PandocError
+items = defun "items"
+ ### (do
+ mb <-unPandocLua getMediaBag
+ let pushItem (fp, mimetype, contents) = do
+ Lua.pushString fp
+ Lua.pushText mimetype
+ Lua.pushByteString $ BL.toStrict contents
+ return (Lua.NumResults 3)
+ Lua.pushIterator pushItem (MB.mediaItems mb))
+ =?> "Iterator triple"
-lookup :: FilePath
- -> PandocLua NumResults
-lookup fp = do
- res <- MB.lookupMedia fp <$> getMediaBag
- liftPandocLua $ case res of
- Nothing -> 1 <$ Lua.pushnil
- Just item -> do
- Lua.push $ MB.mediaMimeType item
- Lua.push $ MB.mediaContents item
- return 2
+-- | Function to lookup a value in the mediabag.
+lookup :: DocumentedFunction PandocError
+lookup = defun "lookup"
+ ### (\fp -> unPandocLua (MB.lookupMedia fp <$> getMediaBag) >>= \case
+ Nothing -> 1 <$ Lua.pushnil
+ Just item -> 2 <$ do
+ Lua.pushText $ MB.mediaMimeType item
+ Lua.pushLazyByteString $ MB.mediaContents item)
+ <#> parameter Lua.peekString "string" "filepath" "path of item to lookup"
+ =?> "MIME type and contents"
-list :: PandocLua NumResults
-list = do
- dirContents <- MB.mediaDirectory <$> getMediaBag
- liftPandocLua $ do
- Lua.newtable
- zipWithM_ addEntry [1..] dirContents
- return 1
+-- | Function listing all mediabag items.
+list :: DocumentedFunction PandocError
+list = defun "list"
+ ### (unPandocLua (MB.mediaDirectory <$> getMediaBag))
+ =#> functionResult (pushPandocList pushEntry) "table" "list of entry triples"
where
- addEntry :: Lua.Integer -> (FilePath, MimeType, Int) -> Lua ()
- addEntry idx (fp, mimeType, contentLength) = do
+ pushEntry :: (FilePath, MimeType, Int) -> LuaE PandocError ()
+ pushEntry (fp, mimeType, contentLength) = do
Lua.newtable
- Lua.push ("path" :: T.Text) *> Lua.push fp *> Lua.rawset (-3)
- Lua.push ("type" :: T.Text) *> Lua.push mimeType *> Lua.rawset (-3)
- Lua.push ("length" :: T.Text) *> Lua.push contentLength *> Lua.rawset (-3)
- Lua.rawseti (-2) idx
+ Lua.pushName "path" *> Lua.pushString fp *> Lua.rawset (-3)
+ Lua.pushName "type" *> Lua.pushText mimeType *> Lua.rawset (-3)
+ Lua.pushName "length" *> Lua.pushIntegral contentLength *> Lua.rawset (-3)
-fetch :: T.Text
- -> PandocLua NumResults
-fetch src = do
- (bs, mimeType) <- fetchItem src
- liftPandocLua . Lua.push $ maybe "" T.unpack mimeType
- liftPandocLua $ Lua.push bs
- return 2 -- returns 2 values: contents, mimetype
+-- | Lua function to retrieve a new item.
+fetch :: DocumentedFunction PandocError
+fetch = defun "fetch"
+ ### (\src -> do
+ (bs, mimeType) <- unPandocLua $ fetchItem src
+ Lua.pushText $ fromMaybe "" mimeType
+ Lua.pushByteString bs
+ return 2)
+ <#> parameter Lua.peekText "string" "src" "URI to fetch"
+ =?> "Returns two string values: the fetched contents and the mimetype."