Lua: simply mediabag module.
Now 'fetch' simply fetches content and mime type. A new 'hashname' function is provided to get a filename based on the sha1 hash of the contents and the mime type.
This commit is contained in:
parent
73c47a44d8
commit
17583cd99d
2 changed files with 43 additions and 19 deletions
|
@ -1130,14 +1130,22 @@ storage. The "media bag" is used when pandoc is called with the
|
|||
local filename = "media/diagram.png"
|
||||
local mt, contents = pandoc.mediabag.lookup(filename)
|
||||
|
||||
[`hashname (mime_type, contents)`]{#mediabag-hashname}
|
||||
|
||||
: Returns a filename with a basename based on the SHA1 has of the
|
||||
contents and an extension based on the mime type.
|
||||
|
||||
Usage:
|
||||
|
||||
local fp = pandoc.mediabag.hashname("plain/text", "foobar")
|
||||
|
||||
[`fetch (source, base_url)`]{#mediabag-fetch}
|
||||
|
||||
: Fetches the given source and inserts it into the media bag
|
||||
using a SHA1 hash of the content as filename. Returns two
|
||||
values: the filename (based on SHA1 hash) and the mime
|
||||
: Fetches the given source from a URL or local file.
|
||||
Returns two values: the contents of the file and the mime
|
||||
type (or an empty string).
|
||||
|
||||
Usage:
|
||||
|
||||
local diagram_url = "https://pandoc.org/diagram.jpg"
|
||||
pandoc.mediabag.fetch(diagram_url, ".")
|
||||
local contents = pandoc.mediabag.fetch(diagram_url, ".")
|
||||
|
|
|
@ -41,13 +41,14 @@ import Data.IORef
|
|||
import Data.Maybe (fromMaybe)
|
||||
import Data.Text (pack)
|
||||
import Foreign.Lua (Lua, FromLuaStack, ToLuaStack, NumResults, liftIO)
|
||||
import Text.Pandoc.Class (fetchMediaResource, readDataFile, runIO,
|
||||
import Text.Pandoc.Class (readDataFile, runIO,
|
||||
runIOorExplode, setUserDataDir, CommonState(..),
|
||||
putCommonState)
|
||||
putCommonState, fetchItem, setMediaBag)
|
||||
import Text.Pandoc.Options (ReaderOptions(readerExtensions))
|
||||
import Text.Pandoc.Lua.StackInstances ()
|
||||
import Text.Pandoc.Readers (Reader (..), getReader)
|
||||
import Text.Pandoc.MIME (MimeType)
|
||||
import Text.Pandoc.MIME (MimeType, extensionFromMimeType)
|
||||
import Data.Digest.Pure.SHA (sha1, showDigest)
|
||||
|
||||
import qualified Foreign.Lua as Lua
|
||||
import qualified Data.ByteString.Lazy as BL
|
||||
|
@ -91,7 +92,8 @@ pushMediaBagModule commonState mediaBagRef = do
|
|||
addFunction "insert" (insertMediaFn mediaBagRef)
|
||||
addFunction "lookup" (lookupMediaFn mediaBagRef)
|
||||
addFunction "list" (mediaDirectoryFn mediaBagRef)
|
||||
addFunction "fetch" (insertResource commonState mediaBagRef)
|
||||
addFunction "fetch" (fetch commonState mediaBagRef)
|
||||
addFunction "hashname" hashnameFn
|
||||
return ()
|
||||
where
|
||||
addFunction name fn = do
|
||||
|
@ -99,6 +101,20 @@ pushMediaBagModule commonState mediaBagRef = do
|
|||
Lua.pushHaskellFunction fn
|
||||
Lua.rawset (-3)
|
||||
|
||||
hashnameFn :: OrNil MimeType
|
||||
-> BL.ByteString
|
||||
-> Lua NumResults
|
||||
hashnameFn nilOrMime contents = do
|
||||
Lua.push (getHashname (toMaybe nilOrMime) contents)
|
||||
return 1
|
||||
|
||||
getHashname :: Maybe MimeType -> BL.ByteString -> String
|
||||
getHashname mbMime bs =
|
||||
let ext = fromMaybe ""
|
||||
(('.':) <$> (mbMime >>= extensionFromMimeType))
|
||||
basename = showDigest $ sha1 bs
|
||||
in basename ++ ext
|
||||
|
||||
insertMediaFn :: IORef MB.MediaBag
|
||||
-> FilePath
|
||||
-> OrNil MimeType
|
||||
|
@ -137,19 +153,19 @@ mediaDirectoryFn mbRef = do
|
|||
Lua.push "length" *> Lua.push contentLength *> Lua.rawset (-3)
|
||||
Lua.rawseti (-2) idx
|
||||
|
||||
insertResource :: CommonState
|
||||
-> IORef MB.MediaBag
|
||||
-> String
|
||||
-> Lua NumResults
|
||||
insertResource commonState mbRef src = do
|
||||
(fp, mimeType, bs) <- liftIO . runIOorExplode $ do
|
||||
fetch :: CommonState
|
||||
-> IORef MB.MediaBag
|
||||
-> String
|
||||
-> Lua NumResults
|
||||
fetch commonState mbRef src = do
|
||||
mediaBag <- liftIO $ readIORef mbRef
|
||||
(bs, mimeType) <- liftIO . runIOorExplode $ do
|
||||
putCommonState commonState
|
||||
fetchMediaResource src
|
||||
liftIO $ print (fp, mimeType) -- TODO DEBUG
|
||||
insertMediaFn mbRef fp (OrNil mimeType) bs
|
||||
Lua.push fp
|
||||
setMediaBag mediaBag
|
||||
fetchItem src
|
||||
Lua.push bs
|
||||
Lua.push $ fromMaybe "" mimeType
|
||||
return 2 -- returns 2 values: name in mediabag, mimetype
|
||||
return 2 -- returns 2 values: contents, mimetype
|
||||
|
||||
--
|
||||
-- Helper types and orphan instances
|
||||
|
|
Loading…
Add table
Reference in a new issue