Lua modules: added pandoc.utils module

A new module `pandoc.utils` has been created. It holds utility functions
like `sha1`, which was moved from the main `pandoc` module.
This commit is contained in:
Albert Krewinkel 2017-12-21 22:30:59 +01:00
parent 5ad719c1fb
commit bd3ea72371
No known key found for this signature in database
GPG key ID: 388DC0B21F631124
6 changed files with 79 additions and 22 deletions

View file

@ -903,4 +903,9 @@ function M.global_filter()
return res return res
end end
------------------------------------------------------------------------
-- Functions which have moved to different modules
local utils = require 'pandoc.utils'
M.sha1 = utils.sha1
return M return M

View file

@ -1405,18 +1405,6 @@ Lua functions for pandoc scripts.
-- the above is equivallent to -- the above is equivallent to
-- return {{Str = Str}} -- return {{Str = Str}}
[`sha1 (contents)`]{#mediabag-sha1}
: Returns the SHA1 has of the contents.
Returns:
- SHA1 hash of the contents.
Usage:
local fp = pandoc.mediabag.sha1("foobar")
[`pipe (command, args, input)`]{#mediabag-sha1} [`pipe (command, args, input)`]{#mediabag-sha1}
: Runs command with arguments, passing it some input, : Runs command with arguments, passing it some input,
@ -1436,9 +1424,28 @@ Lua functions for pandoc scripts.
local output = pandoc.pipe("sed", {"-e","s/a/b/"}, "abc") local output = pandoc.pipe("sed", {"-e","s/a/b/"}, "abc")
# Submodule mediabag
The submodule `mediabag` allows accessing pandoc's media # Module pandoc.utils
This module exposes internal pandoc functions and utility
functions.
[`sha1 (contents)`]{#utils-sha1}
: Returns the SHA1 has of the contents.
Returns:
- SHA1 hash of the contents.
Usage:
local fp = pandoc.utils.sha1("foobar")
# Module pandoc.mediabag
The `pandoc.mediabag` module allows accessing pandoc's media
storage. The "media bag" is used when pandoc is called with the storage. The "media bag" is used when pandoc is called with the
`--extract-media` or `--standalone`/`-s` option. `--extract-media` or `--standalone`/`-s` option.

View file

@ -525,6 +525,7 @@ library
Text.Pandoc.Lua.Init, Text.Pandoc.Lua.Init,
Text.Pandoc.Lua.Module.MediaBag, Text.Pandoc.Lua.Module.MediaBag,
Text.Pandoc.Lua.Module.Pandoc, Text.Pandoc.Lua.Module.Pandoc,
Text.Pandoc.Lua.Module.Utils,
Text.Pandoc.Lua.Packages, Text.Pandoc.Lua.Packages,
Text.Pandoc.Lua.StackInstances, Text.Pandoc.Lua.StackInstances,
Text.Pandoc.Lua.Util, Text.Pandoc.Lua.Util,

View file

@ -32,7 +32,6 @@ module Text.Pandoc.Lua.Module.Pandoc
import Control.Monad (when) import Control.Monad (when)
import Data.Default (Default (..)) import Data.Default (Default (..))
import Data.Digest.Pure.SHA (sha1, showDigest)
import Data.Maybe (fromMaybe) import Data.Maybe (fromMaybe)
import Data.Text (pack) import Data.Text (pack)
import Foreign.Lua (ToLuaStack, FromLuaStack, Lua, NumResults, liftIO) import Foreign.Lua (ToLuaStack, FromLuaStack, Lua, NumResults, liftIO)
@ -59,7 +58,6 @@ pushModule datadir = do
loadScriptFromDataDir datadir "pandoc.lua" loadScriptFromDataDir datadir "pandoc.lua"
addFunction "read" readDoc addFunction "read" readDoc
addFunction "pipe" pipeFn addFunction "pipe" pipeFn
addFunction "sha1" sha1HashFn
addFunction "walk_block" walkBlock addFunction "walk_block" walkBlock
addFunction "walk_inline" walkInline addFunction "walk_inline" walkInline
return 1 return 1
@ -88,12 +86,6 @@ readDoc content formatSpecOrNil = do
Left s -> raiseError (show s) -- error while reading Left s -> raiseError (show s) -- error while reading
_ -> raiseError "Only string formats are supported at the moment." _ -> raiseError "Only string formats are supported at the moment."
sha1HashFn :: BL.ByteString
-> Lua NumResults
sha1HashFn contents = do
Lua.push $ showDigest (sha1 contents)
return 1
-- | Pipes input through a command. -- | Pipes input through a command.
pipeFn :: String pipeFn :: String
-> [String] -> [String]

View file

@ -0,0 +1,50 @@
{-
Copyright © 2017 Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
This program is free software; you can redistribute it and/or modify
it under the terms of the GNU General Public License as published by
the Free Software Foundation; either version 2 of the License, or
(at your option) any later version.
This program is distributed in the hope that it will be useful,
but WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
GNU General Public License for more details.
You should have received a copy of the GNU General Public License
along with this program; if not, write to the Free Software
Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
-}
{- |
Module : Text.Pandoc.Lua.Module.Utils
Copyright : Copyright © 2017 Albert Krewinkel
License : GNU GPL, version 2 or above
Maintainer : Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
Stability : alpha
Utility module for lua, exposing internal helper functions.
-}
module Text.Pandoc.Lua.Module.Utils
( pushModule
) where
import Data.Digest.Pure.SHA (sha1, showDigest)
import Foreign.Lua (Lua, NumResults)
import Text.Pandoc.Lua.StackInstances ()
import Text.Pandoc.Lua.Util (addFunction)
import qualified Data.ByteString.Lazy as BSL
import qualified Foreign.Lua as Lua
-- | Push the "pandoc.utils" module to the lua stack.
pushModule :: Lua NumResults
pushModule = do
Lua.newtable
addFunction "sha1" sha1HashFn
return 1
-- | Calculate the hash of the given contents.
sha1HashFn :: BSL.ByteString
-> Lua String
sha1HashFn = return . showDigest . sha1

View file

@ -43,6 +43,7 @@ import Text.Pandoc.Lua.Util (dostring')
import qualified Foreign.Lua as Lua import qualified Foreign.Lua as Lua
import Text.Pandoc.Lua.Module.Pandoc as Pandoc import Text.Pandoc.Lua.Module.Pandoc as Pandoc
import Text.Pandoc.Lua.Module.MediaBag as MediaBag import Text.Pandoc.Lua.Module.MediaBag as MediaBag
import Text.Pandoc.Lua.Module.Utils as Utils
-- | Parameters used to create lua packages/modules. -- | Parameters used to create lua packages/modules.
data LuaPackageParams = LuaPackageParams data LuaPackageParams = LuaPackageParams
@ -77,6 +78,7 @@ pandocPackageSearcher luaPkgParams pkgName =
"pandoc.mediabag" -> let st = luaPkgCommonState luaPkgParams "pandoc.mediabag" -> let st = luaPkgCommonState luaPkgParams
mbRef = luaPkgMediaBag luaPkgParams mbRef = luaPkgMediaBag luaPkgParams
in pushWrappedHsFun (MediaBag.pushModule st mbRef) in pushWrappedHsFun (MediaBag.pushModule st mbRef)
"pandoc.utils" -> pushWrappedHsFun Utils.pushModule
_ -> searchPureLuaLoader _ -> searchPureLuaLoader
where where
pushWrappedHsFun f = do pushWrappedHsFun f = do