Skip to content

Commit 28486aa

Browse files
committed
Push Captions as userdata, move code to separate module
1 parent 847ee54 commit 28486aa

File tree

7 files changed

+107
-40
lines changed

7 files changed

+107
-40
lines changed

pandoc-lua-marshal.cabal

+1
Original file line numberDiff line numberDiff line change
@@ -79,6 +79,7 @@ library
7979
, Text.Pandoc.Lua.Marshal.Alignment
8080
, Text.Pandoc.Lua.Marshal.Attr
8181
, Text.Pandoc.Lua.Marshal.Block
82+
, Text.Pandoc.Lua.Marshal.Caption
8283
, Text.Pandoc.Lua.Marshal.Cell
8384
, Text.Pandoc.Lua.Marshal.Citation
8485
, Text.Pandoc.Lua.Marshal.CitationMode

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

+2
Original file line numberDiff line numberDiff line change
@@ -11,6 +11,7 @@ module Text.Pandoc.Lua.Marshal.AST
1111
, module Text.Pandoc.Lua.Marshal.Alignment
1212
, module Text.Pandoc.Lua.Marshal.Attr
1313
, module Text.Pandoc.Lua.Marshal.Block
14+
, module Text.Pandoc.Lua.Marshal.Caption
1415
, module Text.Pandoc.Lua.Marshal.Cell
1516
, module Text.Pandoc.Lua.Marshal.Citation
1617
, module Text.Pandoc.Lua.Marshal.CitationMode
@@ -29,6 +30,7 @@ module Text.Pandoc.Lua.Marshal.AST
2930
import Text.Pandoc.Lua.Marshal.Alignment
3031
import Text.Pandoc.Lua.Marshal.Attr
3132
import Text.Pandoc.Lua.Marshal.Block
33+
import Text.Pandoc.Lua.Marshal.Caption
3234
import Text.Pandoc.Lua.Marshal.Cell
3335
import Text.Pandoc.Lua.Marshal.Citation
3436
import Text.Pandoc.Lua.Marshal.CitationMode

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

+2-2
Original file line numberDiff line numberDiff line change
@@ -36,6 +36,7 @@ import Data.Proxy (Proxy (Proxy))
3636
import Data.Text (Text)
3737
import HsLua hiding (Div)
3838
import Text.Pandoc.Lua.Marshal.Attr (peekAttr, pushAttr)
39+
import Text.Pandoc.Lua.Marshal.Caption (peekCaptionFuzzy, pushCaption)
3940
import Text.Pandoc.Lua.Marshal.Content
4041
( Content (..), contentTypeDescription, peekContent, pushContent
4142
, peekDefinitionItem )
@@ -47,8 +48,7 @@ import Text.Pandoc.Lua.Marshal.ListAttributes
4748
( peekListAttributes, pushListAttributes )
4849
import Text.Pandoc.Lua.Marshal.Shared (walkBlocksAndInlines)
4950
import Text.Pandoc.Lua.Marshal.TableParts
50-
( peekCaptionFuzzy, pushCaption
51-
, peekColSpec, pushColSpec
51+
( peekColSpec, pushColSpec
5252
, peekTableBody, pushTableBody
5353
, peekTableFoot, pushTableFoot
5454
, peekTableHead, pushTableHead
+91
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,91 @@
1+
{-# LANGUAGE OverloadedStrings #-}
2+
{- |
3+
Copyright : © 2021-2024 Albert Krewinkel
4+
SPDX-License-Identifier : MIT
5+
Maintainer : Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
6+
7+
Marshaling and unmarshaling of 'Caption' elements.
8+
-}
9+
module Text.Pandoc.Lua.Marshal.Caption
10+
( peekCaption
11+
, peekCaptionFuzzy
12+
, pushCaption
13+
-- * Constructor
14+
, mkCaption
15+
) where
16+
17+
import Control.Applicative ((<|>), optional)
18+
import Control.Monad ((<$!>))
19+
import Data.Aeson (encode)
20+
import Data.Maybe (fromMaybe)
21+
import HsLua
22+
import {-# SOURCE #-} Text.Pandoc.Lua.Marshal.Block
23+
( peekBlocksFuzzy, pushBlocks )
24+
import {-# SOURCE #-} Text.Pandoc.Lua.Marshal.Inline
25+
( peekInlinesFuzzy, pushInlines )
26+
import Text.Pandoc.Definition
27+
28+
-- | Caption object type.
29+
typeCaption :: LuaError e => DocumentedType e Caption
30+
typeCaption = deftype "Caption"
31+
[ operation Eq $ lambda
32+
### liftPure2 (\a b -> fromMaybe False ((==) <$> a <*> b))
33+
<#> parameter (optional . peekCaption) "Caption" "a" ""
34+
<#> parameter (optional . peekCaption) "Caption" "b" ""
35+
=#> functionResult pushBool "boolean" "whether the two are equal"
36+
, operation Tostring $ lambda
37+
### liftPure show
38+
<#> udparam typeCaption "x" ""
39+
=#> functionResult pushString "string" "native Haskell representation"
40+
, operation (CustomOperation "__tojson") $ lambda
41+
### liftPure encode
42+
<#> udparam typeCaption "self" ""
43+
=#> functionResult pushLazyByteString "string" "JSON representation"
44+
]
45+
[ property' "short"
46+
"Inlines|nil"
47+
"short caption used to describe the object"
48+
(maybe pushnil pushInlines, \(Caption short _) -> short)
49+
(peekNilOr peekInlinesFuzzy, \(Caption _ long) shrt -> Caption shrt long)
50+
, property "long" "full caption text"
51+
(pushBlocks, \(Caption _ long) -> long)
52+
(peekBlocksFuzzy, \(Caption short _) long -> Caption short long)
53+
, method $ defun "clone"
54+
### return
55+
<#> parameter peekCaption "Caption" "capt" ""
56+
=#> functionResult pushCaption "Caption" "cloned Caption element"
57+
]
58+
59+
-- | Push Caption element
60+
pushCaption :: LuaError e => Pusher e Caption
61+
pushCaption = pushUD typeCaption
62+
63+
-- | Peek Caption element from userdata.
64+
peekCaption :: LuaError e => Peeker e Caption
65+
peekCaption = peekUD typeCaption
66+
67+
-- | Peek Caption element from a table.
68+
peekCaptionTable :: LuaError e => Peeker e Caption
69+
peekCaptionTable idx = do
70+
short <- optional $ peekFieldRaw peekInlinesFuzzy "short" idx
71+
long <- peekFieldRaw peekBlocksFuzzy "long" idx
72+
return $! Caption short long
73+
74+
peekCaptionFuzzy :: LuaError e => Peeker e Caption
75+
peekCaptionFuzzy = retrieving "Caption" . \idx -> do
76+
peekCaption idx
77+
<|> peekCaptionTable idx
78+
<|> (Caption Nothing <$!> peekBlocksFuzzy idx)
79+
<|> (failPeek =<<
80+
typeMismatchMessage "Caption, list of Blocks, or compatible element" idx)
81+
82+
-- | Constructor for 'Caption'.
83+
mkCaption :: LuaError e => DocumentedFunction e
84+
mkCaption = defun "Caption"
85+
### (\mLong short ->
86+
let long = fromMaybe mempty mLong
87+
in pure (Caption short long))
88+
<#> opt (parameter peekBlocksFuzzy "Blocks" "long" "full caption")
89+
<#> opt (parameter peekInlinesFuzzy "Inlines" "short" "short summary caption")
90+
=#> functionResult pushCaption "Caption" "new Caption object"
91+
#? "Creates a new Caption object."

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

+2-30
Original file line numberDiff line numberDiff line change
@@ -9,10 +9,7 @@ Marshaling/unmarshaling functions of types that are used exclusively
99
with tables.
1010
-}
1111
module Text.Pandoc.Lua.Marshal.TableParts
12-
( peekCaption
13-
, peekCaptionFuzzy
14-
, pushCaption
15-
, peekColSpec
12+
( peekColSpec
1613
, pushColSpec
1714
, peekRow
1815
, peekRowFuzzy
@@ -29,42 +26,17 @@ module Text.Pandoc.Lua.Marshal.TableParts
2926
, mkTableHead
3027
) where
3128

32-
import Control.Applicative ((<|>), optional)
29+
import Control.Applicative (optional)
3330
import Control.Monad ((<$!>))
3431
import HsLua
3532
import Text.Pandoc.Lua.Marshal.Alignment (peekAlignment, pushAlignment)
3633
import Text.Pandoc.Lua.Marshal.Attr (peekAttr, pushAttr)
37-
import {-# SOURCE #-} Text.Pandoc.Lua.Marshal.Block
38-
( peekBlocksFuzzy, pushBlocks )
39-
import {-# SOURCE #-} Text.Pandoc.Lua.Marshal.Inline
40-
( peekInlinesFuzzy, pushInlines )
4134
import Text.Pandoc.Lua.Marshal.List (pushPandocList)
4235
import Text.Pandoc.Lua.Marshal.Row
4336
import Text.Pandoc.Lua.Marshal.TableFoot
4437
import Text.Pandoc.Lua.Marshal.TableHead
4538
import Text.Pandoc.Definition
4639

47-
-- | Push Caption element
48-
pushCaption :: LuaError e => Caption -> LuaE e ()
49-
pushCaption (Caption shortCaption longCaption) = do
50-
newtable
51-
addField "short" (maybe pushnil pushInlines shortCaption)
52-
addField "long" (pushBlocks longCaption)
53-
54-
-- | Peek Caption element
55-
peekCaption :: LuaError e => Peeker e Caption
56-
peekCaption idx = do
57-
short <- optional $ peekFieldRaw peekInlinesFuzzy "short" idx
58-
long <- peekFieldRaw peekBlocksFuzzy "long" idx
59-
return $! Caption short long
60-
61-
peekCaptionFuzzy :: LuaError e => Peeker e Caption
62-
peekCaptionFuzzy = retrieving "Caption" . \idx -> do
63-
peekCaption idx
64-
<|> (Caption Nothing <$!> peekBlocksFuzzy idx)
65-
<|> (failPeek =<<
66-
typeMismatchMessage "Caption, list of Blocks, or compatible element" idx)
67-
6840
-- | Push a ColSpec value as a pair of Alignment and ColWidth.
6941
pushColSpec :: LuaError e => Pusher e ColSpec
7042
pushColSpec = pushPair pushAlignment pushColWidth

test/test-block.lua

+8-8
Original file line numberDiff line numberDiff line change
@@ -181,7 +181,7 @@ return {
181181
local figure = Figure('word', {short='short', long='caption'})
182182
assert.are_equal(figure.caption.long, Blocks 'caption')
183183
assert.are_equal(figure.caption.short, Inlines 'short')
184-
assert.are_equal(type(figure.caption), 'table')
184+
assert.are_equal(type(figure.caption), 'userdata')
185185

186186
figure.caption = {long = 'One day I was...', short = 'My day'}
187187
assert.are_equal(
@@ -334,15 +334,15 @@ return {
334334
test('access caption via property `caption`', function ()
335335
local caption = {long = {Plain 'cap'}}
336336
local tbl = Table(caption, {}, TableHead(), {}, TableFoot())
337-
assert.are_same(tbl.caption, {long = {Plain 'cap'}})
337+
assert.are_same(tbl.caption, Caption{Plain 'cap'})
338338

339339
tbl.caption.short = 'brief'
340340
tbl.caption.long = {Plain 'extended'}
341341

342-
local new_caption = {
343-
short = 'brief',
344-
long = {Plain 'extended'}
345-
}
342+
local new_caption = Caption(
343+
{Plain 'extended'},
344+
'brief'
345+
)
346346
assert.are_equal(
347347
Table(new_caption, {}, TableHead(), {}, TableFoot()),
348348
tbl
@@ -395,9 +395,9 @@ return {
395395
)
396396
end),
397397
test('caption field accepts list of blocks', function ()
398-
local caption = {long = {Plain 'cap'}}
398+
local caption = {Plain 'cap'}
399399
local tbl = Table(caption, {}, TableHead(), {}, TableFoot())
400-
assert.are_same(tbl.caption, {long = {Plain 'cap'}})
400+
assert.are_same(tbl.caption.long, {Plain 'cap'})
401401

402402
tbl.caption = {Plain 'extended'}
403403

test/test-pandoc-lua-marshal.hs

+1
Original file line numberDiff line numberDiff line change
@@ -53,6 +53,7 @@ main = do
5353

5454
blockTests <- run @Lua.Exception $ do
5555
registerDefault
56+
register' mkCaption
5657
translateResultsFromFile "test/test-block.lua"
5758

5859
cellTests <- run @Lua.Exception $ do

0 commit comments

Comments
 (0)