Lua Utils module: add function blocks_to_inlines (#4799)
Exposes a function converting which flattenes a list of blocks into a list of inlines. An example use case would be the conversion of Note elements into other inlines.
This commit is contained in:
parent
bf56181204
commit
fb94c0f6a1
5 changed files with 69 additions and 3 deletions
|
@ -1438,6 +1438,37 @@ Lua functions for pandoc scripts.
|
|||
This module exposes internal pandoc functions and utility
|
||||
functions.
|
||||
|
||||
[`blocks_to_inlines (blocks[, sep])`]{#utils-blocks_to_inlines}
|
||||
|
||||
: Squash a list of blocks into a list of inlines.
|
||||
|
||||
Parameters:
|
||||
|
||||
`blocks`:
|
||||
: List of blocks to be flattened.
|
||||
|
||||
`sep`:
|
||||
: List of inlines inserted as separator between two
|
||||
consecutive blocks; defaults to `{ pandoc.Space(),
|
||||
pandoc.Str'¶', pandoc.Space()}`.
|
||||
|
||||
Returns:
|
||||
|
||||
- ({[Inline][#Inline]}) List of inlines
|
||||
|
||||
Usage:
|
||||
|
||||
local blocks = {
|
||||
pandoc.Para{ pandoc.Str 'Paragraph1' },
|
||||
pandoc.Para{ pandoc.Emph 'Paragraph2' }
|
||||
}
|
||||
local inlines = pandoc.utils.blocks_to_inlines(blocks)
|
||||
-- inlines = {
|
||||
-- pandoc.Str 'Paragraph1',
|
||||
-- pandoc.Space(), pandoc.Str'¶', pandoc.Space(),
|
||||
-- pandoc.Emph{ pandoc.Str 'Paragraph2' }
|
||||
-- }
|
||||
|
||||
[`hierarchicalize (blocks)`]{#utils-hierarchicalize}
|
||||
|
||||
: Convert list of blocks into an hierarchical list. An
|
||||
|
|
|
@ -42,6 +42,7 @@ 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.Builder as B
|
||||
import qualified Text.Pandoc.Filter.JSON as JSONFilter
|
||||
import qualified Text.Pandoc.Shared as Shared
|
||||
|
||||
|
@ -49,6 +50,7 @@ import qualified Text.Pandoc.Shared as Shared
|
|||
pushModule :: Maybe FilePath -> Lua NumResults
|
||||
pushModule mbDatadir = do
|
||||
Lua.newtable
|
||||
addFunction "blocks_to_inlines" blocksToInlines
|
||||
addFunction "hierarchicalize" hierarchicalize
|
||||
addFunction "normalize_date" normalizeDate
|
||||
addFunction "run_json_filter" (runJSONFilter mbDatadir)
|
||||
|
@ -57,6 +59,14 @@ pushModule mbDatadir = do
|
|||
addFunction "to_roman_numeral" toRomanNumeral
|
||||
return 1
|
||||
|
||||
-- | Squashes a list of blocks into inlines.
|
||||
blocksToInlines :: [Block] -> Lua.Optional [Inline] -> Lua [Inline]
|
||||
blocksToInlines blks optSep = do
|
||||
let sep = case Lua.fromOptional optSep of
|
||||
Just x -> B.fromList x
|
||||
Nothing -> Shared.defaultBlocksSeparator
|
||||
return $ B.toList (Shared.blocksToInlinesWithSep sep blks)
|
||||
|
||||
-- | Convert list of Pandoc blocks into (hierarchical) list of Elements.
|
||||
hierarchicalize :: [Block] -> Lua [Shared.Element]
|
||||
hierarchicalize = return . Shared.hierarchicalize
|
||||
|
|
|
@ -94,6 +94,8 @@ module Text.Pandoc.Shared (
|
|||
-- * for squashing blocks
|
||||
blocksToInlines,
|
||||
blocksToInlines',
|
||||
blocksToInlinesWithSep,
|
||||
defaultBlocksSeparator,
|
||||
-- * Safe read
|
||||
safeRead,
|
||||
-- * Temp directory
|
||||
|
@ -757,12 +759,19 @@ blocksToInlinesWithSep sep =
|
|||
mconcat . intersperse sep . map blockToInlines
|
||||
|
||||
blocksToInlines' :: [Block] -> Inlines
|
||||
blocksToInlines' = blocksToInlinesWithSep parSep
|
||||
where parSep = B.space <> B.str "¶" <> B.space
|
||||
blocksToInlines' = blocksToInlinesWithSep defaultBlocksSeparator
|
||||
|
||||
blocksToInlines :: [Block] -> [Inline]
|
||||
blocksToInlines = B.toList . blocksToInlines'
|
||||
|
||||
-- | Inline elements used to separate blocks when squashing blocks into
|
||||
-- inlines.
|
||||
defaultBlocksSeparator :: Inlines
|
||||
defaultBlocksSeparator =
|
||||
-- This is used in the pandoc.utils.blocks_to_inlines function. Docs
|
||||
-- there should be updated if this is changed.
|
||||
B.space <> B.str "¶" <> B.space
|
||||
|
||||
|
||||
--
|
||||
-- Safe read
|
||||
|
|
|
@ -109,7 +109,8 @@ tests = map (localOption (QuickCheckTests 20))
|
|||
assertFilterConversion "pandoc.utils doesn't work as expected."
|
||||
"test-pandoc-utils.lua"
|
||||
(doc $ para "doesn't matter")
|
||||
(doc $ mconcat [ plain (str "hierarchicalize: OK")
|
||||
(doc $ mconcat [ plain (str "blocks_to_inlines: OK")
|
||||
, plain (str "hierarchicalize: OK")
|
||||
, plain (str "normalize_date: OK")
|
||||
, plain (str "pipe: OK")
|
||||
, plain (str "failing pipe: OK")
|
||||
|
|
|
@ -1,5 +1,19 @@
|
|||
utils = require 'pandoc.utils'
|
||||
|
||||
-- Squash blocks to inlines
|
||||
------------------------------------------------------------------------
|
||||
function test_blocks_to_inlines ()
|
||||
local blocks = {
|
||||
pandoc.Para{ pandoc.Str 'Paragraph1' },
|
||||
pandoc.Para{ pandoc.Emph 'Paragraph2' }
|
||||
}
|
||||
local inlines = utils.blocks_to_inlines(blocks, {pandoc.LineBreak()})
|
||||
return #inlines == 3
|
||||
and inlines[1].text == "Paragraph1"
|
||||
and inlines[2].t == 'LineBreak'
|
||||
and inlines[3].content[1].text == "Paragraph2"
|
||||
end
|
||||
|
||||
-- hierarchicalize
|
||||
------------------------------------------------------------------------
|
||||
function test_hierarchicalize ()
|
||||
|
@ -110,6 +124,7 @@ end
|
|||
|
||||
function Para (el)
|
||||
return {
|
||||
pandoc.Plain{pandoc.Str("blocks_to_inlines: " .. run(test_blocks_to_inlines))},
|
||||
pandoc.Plain{pandoc.Str("hierarchicalize: " .. run(test_hierarchicalize))},
|
||||
pandoc.Plain{pandoc.Str("normalize_date: " .. run(test_normalize_date))},
|
||||
pandoc.Plain{pandoc.Str("pipe: " .. run(test_pipe))},
|
||||
|
|
Loading…
Add table
Reference in a new issue