| 1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
 | {-# LANGUAGE OverloadedStrings #-}
{- |
   Module      : Text.Pandoc.Lua.Module.MediaBag
   Copyright   : Copyright © 2017-2020 Albert Krewinkel
   License     : GNU GPL, version 2 or above
   Maintainer  : Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
   Stability   : alpha
The lua module @pandoc.mediabag@.
-}
module Text.Pandoc.Lua.Module.MediaBag
  ( pushModule
  ) where
import Control.Monad (zipWithM_)
import Foreign.Lua (Lua, NumResults, Optional)
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.MIME (MimeType)
import qualified Data.ByteString.Lazy as BL
import qualified Data.Text as T
import qualified Foreign.Lua 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" insertMediaFn
  addFunction "items" items
  addFunction "lookup" lookupMediaFn
  addFunction "list" mediaDirectoryFn
  addFunction "fetch" fetch
  return 1
-- | 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 all items from the media bag.
empty :: PandocLua NumResults
empty = 0 <$ modifyCommonState (\st -> st { stMediaBag = mempty })
-- | Insert a new item into the media bag.
insertMediaFn :: FilePath
              -> Optional MimeType
              -> BL.ByteString
              -> PandocLua NumResults
insertMediaFn fp optionalMime contents = do
  mb <- getMediaBag
  setMediaBag $ MB.insertMedia fp (Lua.fromOptional optionalMime) contents mb
  return (Lua.NumResults 0)
-- | Returns iterator values to be used with a Lua @for@ loop.
items :: PandocLua NumResults
items = getMediaBag >>= liftPandocLua . pushIterator
lookupMediaFn :: FilePath
              -> PandocLua NumResults
lookupMediaFn fp = do
  res <- MB.lookupMedia fp <$> getMediaBag
  liftPandocLua $ case res of
    Nothing -> 1 <$ Lua.pushnil
    Just (mimeType, contents) -> do
      Lua.push mimeType
      Lua.push contents
      return 2
mediaDirectoryFn :: PandocLua NumResults
mediaDirectoryFn = do
  dirContents <- MB.mediaDirectory <$> getMediaBag
  liftPandocLua $ do
    Lua.newtable
    zipWithM_ addEntry [1..] dirContents
  return 1
 where
  addEntry :: Lua.Integer -> (FilePath, MimeType, Int) -> Lua ()
  addEntry idx (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
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
 |