Skip to content

Commit a52b6c2

Browse files
committed
Add method normalize to Pandoc objects
This returns a normalized document by merging adjacent spaces in inlines and by modifying tables.
1 parent 28486aa commit a52b6c2

File tree

2 files changed

+68
-1
lines changed

2 files changed

+68
-1
lines changed

src/Text/Pandoc/Lua/Marshal/Pandoc.hs

+26-1
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,7 @@
1+
{-# LANGUAGE FlexibleContexts #-}
2+
{-# LANGUAGE LambdaCase #-}
13
{-# LANGUAGE OverloadedStrings #-}
4+
{-# LANGUAGE TypeApplications #-}
25
{- |
36
Copyright : © 2021-2024 Albert Krewinkel
47
SPDX-License-Identifier : MIT
@@ -25,12 +28,15 @@ import Control.Monad ((<$!>))
2528
import Data.Aeson (encode)
2629
import Data.Maybe (fromMaybe)
2730
import HsLua
31+
import Text.Pandoc.Definition (Pandoc (..), Meta (..), nullMeta)
2832
import Text.Pandoc.Lua.Marshal.Block (peekBlocksFuzzy, pushBlocks)
2933
import Text.Pandoc.Lua.Marshal.Filter
3034
import Text.Pandoc.Lua.Marshal.MetaValue (peekMetaValue, pushMetaValue)
3135
import Text.Pandoc.Lua.Marshal.Shared (walkBlocksAndInlines)
3236
import Text.Pandoc.Lua.Walk (applyStraight)
33-
import Text.Pandoc.Definition (Pandoc (..), Meta (..), nullMeta)
37+
import Text.Pandoc.Walk (Walkable (walk))
38+
import qualified Data.Foldable as Foldable
39+
import qualified Text.Pandoc.Builder as B
3440

3541
-- | Pushes a 'Pandoc' value as userdata.
3642
pushPandoc :: LuaError e => Pusher e Pandoc
@@ -74,6 +80,11 @@ typePandoc = deftype "Pandoc"
7480
<#> parameter peekPandoc "Pandoc" "doc" "self"
7581
=#> functionResult pushPandoc "Pandoc" "cloned Pandoc document"
7682

83+
, method $ defun "normalize"
84+
### liftPure normalize
85+
<#> udparam typePandoc "self" ""
86+
=#> udresult typePandoc "cloned and normalized document"
87+
7788
, method $ defun "walk"
7889
### flip applyFully
7990
<#> parameter peekPandoc "Pandoc" "self" ""
@@ -149,3 +160,17 @@ applyFully filter' doc = case filterWalkingOrder filter' of
149160
WalkTopdown -> applyPandocFunction filter' doc
150161
>>= applyMetaFunction filter'
151162
>>= walkBlocksAndInlines filter'
163+
164+
-- | Normalize a document
165+
normalize :: (Walkable [B.Inline] a, Walkable B.Block a) => a -> a
166+
normalize =
167+
let normalizeBlock = \case
168+
B.Table attr capt specs th tbs tf ->
169+
let twidth = length specs
170+
th' = B.normalizeTableHead twidth th
171+
tbs' = map (B.normalizeTableBody twidth) tbs
172+
tf' = B.normalizeTableFoot twidth tf
173+
in B.Table attr capt specs th' tbs' tf'
174+
x -> x
175+
in walk normalizeBlock .
176+
walk (B.toList . mconcat . map (B.singleton @B.Inline))

test/test-pandoc.lua

+42
Original file line numberDiff line numberDiff line change
@@ -60,6 +60,48 @@ return {
6060
assert.are_same(Blocks{'different'}, copy.blocks)
6161
end),
6262
},
63+
group 'normalize' {
64+
test('removes repeated whitespace', function ()
65+
local doc = Pandoc{
66+
Plain{'before', Space(), SoftBreak(), 'after'}
67+
}
68+
assert.are_equal(
69+
Blocks{Plain{'before', SoftBreak(), 'after'}},
70+
doc:normalize().blocks
71+
)
72+
end),
73+
test('normalizes table', function ()
74+
local attr = Attr('test')
75+
local caption = Blocks('Sample caption')
76+
local colspecs = {{'AlignDefault', 0.5}, {'AlignLeft', 0.5}}
77+
local thead = TableHead({Row{Cell'header cell'}})
78+
local tbody = {
79+
attr = Attr(),
80+
body = List{
81+
Row{Cell'body cell 1', Cell'body cell 2'},
82+
Row{Cell('hi')}},
83+
},
84+
head = List{},
85+
row_head_columns = 0,
86+
}
87+
local tfoot = TableFoot()
88+
local tbl = Table(caption, colspecs, thead, {tbody}, tfoot)
89+
print(tbl.bodies)
90+
local expected_body = tbody
91+
expected_body.body[2][2]:insert(Cell{})
92+
local doc = Pandoc{tbl}
93+
assert.are_same(
94+
Table(
95+
caption,
96+
colspecs,
97+
TableHead({Row{Cell'header cell', Cell{}}}),
98+
{expected_body},
99+
tfoot
100+
),
101+
doc:normalize().blocks[1]
102+
)
103+
end)
104+
},
63105
group 'walk' {
64106
test('uses `Meta` function', function ()
65107
local meta = {

0 commit comments

Comments
 (0)