aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Lua/Marshaling/ListAttributes.hs
blob: 5a66086442036b5ca1a301b5ac1127ac6d358610 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
{-# LANGUAGE OverloadedStrings    #-}
{-# LANGUAGE TupleSections        #-}
{- |
Module      : Text.Pandoc.Lua.Marshaling.ListAttributes
Copyright   : © 2021 Albert Krewinkel
License     : GNU GPL, version 2 or above
Maintainer  : Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>

Marshaling/unmarshaling functions and constructor for 'ListAttributes'
values.
-}
module Text.Pandoc.Lua.Marshaling.ListAttributes
  ( typeListAttributes
  , peekListAttributes
  , pushListAttributes
  , mkListAttributes
  ) where

import Data.Maybe (fromMaybe)
import HsLua
import Text.Pandoc.Definition ( ListAttributes, ListNumberStyle (DefaultStyle)
                              , ListNumberDelim (DefaultDelim))

typeListAttributes :: LuaError e => DocumentedType e ListAttributes
typeListAttributes = deftype "ListAttributes"
  [ operation Eq $ lambda
    ### liftPure2 (==)
    <#> parameter peekListAttributes "a" "ListAttributes" ""
    <#> parameter peekListAttributes "b" "ListAttributes" ""
    =#> functionResult pushBool "boolean" "whether the two are equal"
  ]
  [ property "start" "number of the first list item"
      (pushIntegral, \(start,_,_) -> start)
      (peekIntegral, \(_,style,delim) -> (,style,delim))
  , property "style" "style used for list numbering"
      (pushString . show, \(_,classes,_) -> classes)
      (peekRead, \(start,_,delim) -> (start,,delim))
  , property "delimiter" "delimiter of list numbers"
      (pushString . show, \(_,_,delim) -> delim)
      (peekRead, \(start,style,_) -> (start,style,))
  , method $ defun "clone"
    ### return
    <#> udparam typeListAttributes "a" ""
    =#> functionResult (pushUD typeListAttributes) "ListAttributes"
          "cloned ListAttributes value"
  ]

-- | Pushes a 'ListAttributes' value as userdata object.
pushListAttributes :: LuaError e => Pusher e ListAttributes
pushListAttributes = pushUD typeListAttributes

-- | Retrieve a 'ListAttributes' triple, either from userdata or from a
-- Lua tuple.
peekListAttributes :: LuaError e => Peeker e ListAttributes
peekListAttributes = retrieving "ListAttributes" . choice
  [ peekUD typeListAttributes
  , peekTriple peekIntegral peekRead peekRead
  ]

-- | Constructor for a new 'ListAttributes' value.
mkListAttributes :: LuaError e => DocumentedFunction e
mkListAttributes = defun "ListAttributes"
  ### liftPure3 (\mstart mstyle mdelim ->
                   ( fromMaybe 1 mstart
                   , fromMaybe DefaultStyle mstyle
                   , fromMaybe DefaultDelim mdelim
                   ))
  <#> optionalParameter peekIntegral "integer" "start" "number of first item"
  <#> optionalParameter peekRead "string" "style" "list numbering style"
  <#> optionalParameter peekRead "string" "delimiter" "list number delimiter"
  =#> functionResult pushListAttributes "ListAttributes" "new ListAttributes"
  #? "Creates a new ListAttributes object."