Skip to content

Commit

Permalink
Lua Utils module: add function blocks_to_inlines (#4799)
Browse files Browse the repository at this point in the history
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.
  • Loading branch information
tarleb authored and jgm committed Jul 30, 2018
1 parent bf56181 commit fb94c0f
Show file tree
Hide file tree
Showing 5 changed files with 69 additions and 3 deletions.
31 changes: 31 additions & 0 deletions doc/lua-filters.md
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down
10 changes: 10 additions & 0 deletions src/Text/Pandoc/Lua/Module/Utils.hs
Original file line number Diff line number Diff line change
Expand Up @@ -42,13 +42,15 @@ 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

-- | Push the "pandoc.utils" module to the lua stack.
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)
Expand All @@ -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
Expand Down
13 changes: 11 additions & 2 deletions src/Text/Pandoc/Shared.hs
Original file line number Diff line number Diff line change
Expand Up @@ -94,6 +94,8 @@ module Text.Pandoc.Shared (
-- * for squashing blocks
blocksToInlines,
blocksToInlines',
blocksToInlinesWithSep,
defaultBlocksSeparator,
-- * Safe read
safeRead,
-- * Temp directory
Expand Down Expand Up @@ -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
Expand Down
3 changes: 2 additions & 1 deletion test/Tests/Lua.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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")
Expand Down
15 changes: 15 additions & 0 deletions test/lua/test-pandoc-utils.lua
Original file line number Diff line number Diff line change
@@ -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 ()
Expand Down Expand Up @@ -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))},
Expand Down

0 comments on commit fb94c0f

Please sign in to comment.