1
+ {-# LANGUAGE FlexibleContexts #-}
2
+ {-# LANGUAGE LambdaCase #-}
1
3
{-# LANGUAGE OverloadedStrings #-}
4
+ {-# LANGUAGE TypeApplications #-}
2
5
{- |
3
6
Copyright : © 2021-2024 Albert Krewinkel
4
7
SPDX-License-Identifier : MIT
@@ -25,12 +28,15 @@ import Control.Monad ((<$!>))
25
28
import Data.Aeson (encode )
26
29
import Data.Maybe (fromMaybe )
27
30
import HsLua
31
+ import Text.Pandoc.Definition (Pandoc (.. ), Meta (.. ), nullMeta )
28
32
import Text.Pandoc.Lua.Marshal.Block (peekBlocksFuzzy , pushBlocks )
29
33
import Text.Pandoc.Lua.Marshal.Filter
30
34
import Text.Pandoc.Lua.Marshal.MetaValue (peekMetaValue , pushMetaValue )
31
35
import Text.Pandoc.Lua.Marshal.Shared (walkBlocksAndInlines )
32
36
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
34
40
35
41
-- | Pushes a 'Pandoc' value as userdata.
36
42
pushPandoc :: LuaError e => Pusher e Pandoc
@@ -74,6 +80,11 @@ typePandoc = deftype "Pandoc"
74
80
<#> parameter peekPandoc " Pandoc" " doc" " self"
75
81
=#> functionResult pushPandoc " Pandoc" " cloned Pandoc document"
76
82
83
+ , method $ defun " normalize"
84
+ ### liftPure normalize
85
+ <#> udparam typePandoc " self" " "
86
+ =#> udresult typePandoc " cloned and normalized document"
87
+
77
88
, method $ defun " walk"
78
89
### flip applyFully
79
90
<#> parameter peekPandoc " Pandoc" " self" " "
@@ -149,3 +160,17 @@ applyFully filter' doc = case filterWalkingOrder filter' of
149
160
WalkTopdown -> applyPandocFunction filter' doc
150
161
>>= applyMetaFunction filter'
151
162
>>= 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 ))
0 commit comments