aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Lua/Module/MediaBag.hs
blob: fb055101e0c49373ae7831f10080bb0ea76ea681 (plain)
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
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
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>

The Lua module @pandoc.mediabag@.
-}
module Text.Pandoc.Lua.Module.MediaBag
  ( documentedModule
  ) where

import Prelude hiding (lookup)
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.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 HsLua as Lua
import qualified Text.Pandoc.MediaBag as MB

--
-- MediaBag submodule
--
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 :: 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 :: DocumentedFunction PandocError
empty = defun "empty"
  ### unPandocLua (modifyCommonState (\st -> st { stMediaBag = mempty }))
  =#> []

-- | Insert a new item into the media bag.
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 :: 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"

-- | 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"

-- | Function listing all mediabag items.
list :: DocumentedFunction PandocError
list = defun "list"
  ### (unPandocLua (MB.mediaDirectory <$> getMediaBag))
  =#> functionResult (pushPandocList pushEntry) "table" "list of entry triples"
 where
  pushEntry :: (FilePath, MimeType, Int) -> LuaE PandocError ()
  pushEntry (fp, mimeType, contentLength) = do
    Lua.newtable
    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)

-- | 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."