Lua modules: add function pandoc.utils.run_json_filter
Runs a JSON filter on a Pandoc document.
This commit is contained in:
parent
5d49cbd35e
commit
8d5422f36b
3 changed files with 59 additions and 4 deletions
|
@ -1433,6 +1433,37 @@ functions.
|
|||
print(table.concat(elements[1].numbering, '.')) -- 0.1
|
||||
print(table.concat(elements[2].numbering, '.')) -- 0.2
|
||||
|
||||
[`run_json_filter (doc, filter[, args])`]{#utils-run_json_filter}
|
||||
|
||||
: Filter the given doc by passing it through the a JSON filter.
|
||||
|
||||
Parameters:
|
||||
|
||||
`doc`:
|
||||
: the Pandoc document to filter
|
||||
|
||||
`filter`:
|
||||
: filter to run
|
||||
|
||||
`args`:
|
||||
: list of arguments passed to the filter. Defaults to
|
||||
`{FORMAT}`.
|
||||
|
||||
Returns:
|
||||
|
||||
- ([Pandoc](#Pandoc)) Filtered document
|
||||
|
||||
Usage:
|
||||
|
||||
-- Assumes `some_blocks` contains blocks for which a
|
||||
-- separate literature section is required.
|
||||
local sub_doc = pandoc.Pandoc(some_blocks, metadata)
|
||||
sub_doc_with_bib = pandoc.utils.run_json_filter(
|
||||
sub_doc,
|
||||
'pandoc-citeproc'
|
||||
)
|
||||
some_blocks = sub_doc.blocks -- some blocks with bib
|
||||
|
||||
[`normalize_date (date_string)`]{#utils-normalize_date}
|
||||
|
||||
: Parse a date and convert (if possible) to "YYYY-MM-DD"
|
||||
|
|
|
@ -30,22 +30,26 @@ module Text.Pandoc.Lua.Module.Utils
|
|||
) where
|
||||
|
||||
import Control.Applicative ((<|>))
|
||||
import Data.Default (def)
|
||||
import Foreign.Lua (FromLuaStack, Lua, LuaInteger, NumResults)
|
||||
import Text.Pandoc.Class (runIO, setUserDataDir)
|
||||
import Text.Pandoc.Definition (Pandoc, Meta, MetaValue, Block, Inline)
|
||||
import Text.Pandoc.Lua.StackInstances ()
|
||||
import Text.Pandoc.Lua.Util (addFunction)
|
||||
import Text.Pandoc.Lua.Util (addFunction, popValue)
|
||||
|
||||
import qualified Data.Digest.Pure.SHA as SHA
|
||||
import qualified Data.ByteString.Lazy as BSL
|
||||
import qualified Foreign.Lua as Lua
|
||||
import qualified Text.Pandoc.Filter.Json as JsonFilter
|
||||
import qualified Text.Pandoc.Shared as Shared
|
||||
|
||||
-- | Push the "pandoc.utils" module to the lua stack.
|
||||
pushModule :: Lua NumResults
|
||||
pushModule = do
|
||||
pushModule :: Maybe FilePath -> Lua NumResults
|
||||
pushModule mbDatadir = do
|
||||
Lua.newtable
|
||||
addFunction "hierarchicalize" hierarchicalize
|
||||
addFunction "normalize_date" normalizeDate
|
||||
addFunction "run_json_filter" (runJsonFilter mbDatadir)
|
||||
addFunction "sha1" sha1
|
||||
addFunction "stringify" stringify
|
||||
addFunction "to_roman_numeral" toRomanNumeral
|
||||
|
@ -62,6 +66,25 @@ hierarchicalize = return . Shared.hierarchicalize
|
|||
normalizeDate :: String -> Lua (Lua.Optional String)
|
||||
normalizeDate = return . Lua.Optional . Shared.normalizeDate
|
||||
|
||||
-- | Run a JSON filter on the given document.
|
||||
runJsonFilter :: Maybe FilePath
|
||||
-> Pandoc
|
||||
-> FilePath
|
||||
-> Lua.Optional [String]
|
||||
-> Lua NumResults
|
||||
runJsonFilter mbDatadir doc filterFile optArgs = do
|
||||
args <- case Lua.fromOptional optArgs of
|
||||
Just x -> return x
|
||||
Nothing -> do
|
||||
Lua.getglobal "FORMAT"
|
||||
(:[]) <$> popValue
|
||||
filterRes <- Lua.liftIO . runIO $ do
|
||||
setUserDataDir mbDatadir
|
||||
JsonFilter.apply def args filterFile doc
|
||||
case filterRes of
|
||||
Left err -> Lua.raiseError (show err)
|
||||
Right d -> (1 :: NumResults) <$ Lua.push d
|
||||
|
||||
-- | Calculate the hash of the given contents.
|
||||
sha1 :: BSL.ByteString
|
||||
-> Lua String
|
||||
|
|
|
@ -78,7 +78,8 @@ pandocPackageSearcher luaPkgParams pkgName =
|
|||
"pandoc.mediabag" -> let st = luaPkgCommonState luaPkgParams
|
||||
mbRef = luaPkgMediaBag luaPkgParams
|
||||
in pushWrappedHsFun (MediaBag.pushModule st mbRef)
|
||||
"pandoc.utils" -> pushWrappedHsFun Utils.pushModule
|
||||
"pandoc.utils" -> let datadirMb = luaPkgDataDir luaPkgParams
|
||||
in pushWrappedHsFun (Utils.pushModule datadirMb)
|
||||
_ -> searchPureLuaLoader
|
||||
where
|
||||
pushWrappedHsFun f = do
|
||||
|
|
Loading…
Add table
Reference in a new issue