aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Lua/Marshaling/Attr.hs
blob: 97e702e354b86fab1d8c1328632cae3eec2b0ce6 (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
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
{-# LANGUAGE BangPatterns         #-}
{-# LANGUAGE LambdaCase           #-}
{-# LANGUAGE OverloadedStrings    #-}
{-# LANGUAGE ScopedTypeVariables  #-}
{-# LANGUAGE TupleSections        #-}
{-# LANGUAGE TypeApplications     #-}
{- |
Module      : Text.Pandoc.Lua.Marshaling.Attr
Copyright   : © 2012-2021 John MacFarlane
              © 2017-2021 Albert Krewinkel
License     : GNU GPL, version 2 or above

Maintainer  : Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
Stability   : alpha

Marshaling/unmarshaling instances for document AST elements.
-}
module Text.Pandoc.Lua.Marshaling.Attr
  ( typeAttr
  , peekAttr
  , pushAttr
  , mkAttr
  , mkAttributeList
  ) where

import Control.Applicative ((<|>), optional)
import Control.Monad ((<$!>))
import Data.Maybe (fromMaybe)
import Data.Text (Text)
import HsLua
import HsLua.Marshalling.Peekers (peekIndexRaw)
import Safe (atMay)
import Text.Pandoc.Definition (Attr, nullAttr)
import Text.Pandoc.Lua.Marshaling.List (pushPandocList)

import qualified Data.Text as T

typeAttr :: LuaError e => DocumentedType e Attr
typeAttr = deftype "Attr"
  [ operation Eq $ lambda
    ### liftPure2 (==)
    <#> parameter peekAttr "a1" "Attr" ""
    <#> parameter peekAttr "a2" "Attr" ""
    =#> functionResult pushBool "boolean" "whether the two are equal"
  , operation Tostring $ lambda
    ### liftPure show
    <#> parameter peekAttr "Attr" "attr" ""
    =#> functionResult pushString "string" "native Haskell representation"
  ]
  [ property "identifier" "element identifier"
      (pushText, \(ident,_,_) -> ident)
      (peekText, \(_,cls,kv) -> (,cls,kv))
  , property "classes" "element classes"
      (pushPandocList pushText, \(_,classes,_) -> classes)
      (peekList peekText, \(ident,_,kv) -> (ident,,kv))
  , property "attributes" "various element attributes"
      (pushAttribs, \(_,_,attribs) -> attribs)
      (peekAttribs, \(ident,cls,_) -> (ident,cls,))
  , method $ defun "clone"
    ### return
    <#> parameter peekAttr "attr" "Attr" ""
    =#> functionResult pushAttr "Attr" "new Attr element"
  , readonly "tag" "element type tag (always 'Attr')"
      (pushText, const "Attr")

  , alias "t" "alias for `tag`" ["tag"]
  ]

pushAttr :: LuaError e => Pusher e Attr
pushAttr = pushUD typeAttr

peekAttribs :: LuaError e => Peeker e [(Text,Text)]
peekAttribs idx = liftLua (ltype idx) >>= \case
  TypeUserdata -> peekUD typeAttributeList idx
  TypeTable    -> liftLua (rawlen idx) >>= \case
    0 -> peekKeyValuePairs peekText peekText idx
    _ -> peekList (peekPair peekText peekText) idx
  _            -> failPeek "unsupported type"

pushAttribs :: LuaError e => Pusher e [(Text, Text)]
pushAttribs = pushUD typeAttributeList

typeAttributeList :: LuaError e => DocumentedType e [(Text, Text)]
typeAttributeList = deftype "AttributeList"
  [ operation Eq $ lambda
    ### liftPure2 (==)
    <#> parameter peekAttribs "a1" "AttributeList" ""
    <#> parameter peekAttribs "a2" "AttributeList" ""
    =#> functionResult pushBool "boolean" "whether the two are equal"

  , operation Index $ lambda
    ### liftPure2 lookupKey
    <#> udparam typeAttributeList "t" "attributes list"
    <#> parameter peekKey "string|integer" "key" "lookup key"
    =#> functionResult (maybe pushnil pushAttribute) "string|table"
          "attribute value"

  , operation Newindex $ lambda
    ### setKey
    <#> udparam typeAttributeList "t" "attributes list"
    <#> parameter peekKey "string|integer" "key" "lookup key"
    <#> optionalParameter peekAttribute "string|nil" "value" "new value"
    =#> []

  , operation Len $ lambda
    ### liftPure length
    <#> udparam typeAttributeList "t" "attributes list"
    =#> functionResult pushIntegral "integer" "number of attributes in list"

  , operation Pairs $ lambda
    ### pushIterator (\(k, v) -> 2 <$ pushText k <* pushText v)
    <#> udparam typeAttributeList "t" "attributes list"
    =?> "iterator triple"

  , operation Tostring $ lambda
    ### liftPure show
    <#> udparam typeAttributeList "t" "attributes list"
    =#> functionResult pushString "string" ""
  ]
  []

data Key = StringKey Text | IntKey Int

peekKey :: LuaError e => Peeker e (Maybe Key)
peekKey idx = liftLua (ltype idx) >>= \case
  TypeNumber -> Just . IntKey <$!> peekIntegral idx
  TypeString -> Just . StringKey <$!> peekText idx
  _          -> return Nothing

data Attribute
  = AttributePair (Text, Text)
  | AttributeValue Text

pushAttribute :: LuaError e => Pusher e Attribute
pushAttribute = \case
  (AttributePair kv) -> pushPair pushText pushText kv
  (AttributeValue v) -> pushText v

-- | Retrieve an 'Attribute'.
peekAttribute :: LuaError e => Peeker e Attribute
peekAttribute idx = (AttributeValue <$!> peekText idx)
  <|> (AttributePair <$!> peekPair peekText peekText idx)

lookupKey :: [(Text,Text)] -> Maybe Key -> Maybe Attribute
lookupKey !kvs = \case
  Just (StringKey str) -> AttributeValue <$!> lookup str kvs
  Just (IntKey n)      -> AttributePair <$!> atMay kvs (n - 1)
  Nothing              -> Nothing

setKey :: forall e. LuaError e
       => [(Text, Text)] -> Maybe Key -> Maybe Attribute
       -> LuaE e ()
setKey kvs mbKey mbValue = case mbKey of
  Just (StringKey str) ->
    case break ((== str) . fst) kvs of
      (prefix, _:suffix) -> case mbValue of
        Nothing -> setNew $ prefix ++ suffix
        Just (AttributeValue value) -> setNew $ prefix ++ (str, value):suffix
        _ -> failLua "invalid attribute value"
      _  -> case mbValue of
        Nothing -> return ()
        Just (AttributeValue value) -> setNew (kvs ++ [(str, value)])
        _ -> failLua "invalid attribute value"
  Just (IntKey idx) ->
    case splitAt (idx - 1) kvs of
      (prefix, (k,_):suffix) -> setNew $ case mbValue of
        Nothing -> prefix ++ suffix
        Just (AttributePair kv) -> prefix ++ kv : suffix
        Just (AttributeValue v) -> prefix ++ (k, v) : suffix
      (prefix, []) -> case mbValue of
        Nothing -> setNew prefix
        Just (AttributePair kv) -> setNew $ prefix ++ [kv]
        _ -> failLua $ "trying to set an attribute key-value pair, "
             ++ "but got a single string instead."

  _  -> failLua "invalid attribute key"
  where
    setNew :: [(Text, Text)] -> LuaE e ()
    setNew new =
      putuserdata (nthBottom 1) (udName @e typeAttributeList) new >>= \case
        True -> return ()
        False -> failLua "failed to modify attributes list"

peekAttr :: LuaError e => Peeker e Attr
peekAttr idx = retrieving "Attr" $ liftLua (ltype idx) >>= \case
  TypeString -> (,[],[]) <$!> peekText idx -- treat string as ID
  TypeUserdata -> peekUD typeAttr idx
  TypeTable -> peekAttrTable idx
  x -> liftLua . failLua $ "Cannot get Attr from " ++ show x

-- | Helper function which gets an Attr from a Lua table.
peekAttrTable :: LuaError e => Peeker e Attr
peekAttrTable idx = do
  len' <- liftLua $ rawlen idx
  let peekClasses = peekList peekText
  if len' > 0
    then do
      ident <- peekIndexRaw 1 peekText idx
      classes <- fromMaybe [] <$!> optional (peekIndexRaw 2 peekClasses idx)
      attribs <- fromMaybe [] <$!> optional (peekIndexRaw 3 peekAttribs idx)
      return $ ident `seq` classes `seq` attribs `seq`
        (ident, classes, attribs)
    else retrieving "HTML-like attributes" $ do
      kvs <- peekKeyValuePairs peekText peekText idx
      let ident = fromMaybe "" $ lookup "id" kvs
      let classes = maybe [] T.words $ lookup "class" kvs
      let attribs = filter ((`notElem` ["id", "class"]) . fst) kvs
      return $ ident `seq` classes `seq` attribs `seq`
        (ident, classes, attribs)

-- | Constructor for 'Attr'.
mkAttr :: LuaError e => DocumentedFunction e
mkAttr = defun "Attr"
  ### (ltype (nthBottom 1) >>= \case
          TypeString -> forcePeek $ do
            mident <- optional (peekText (nthBottom 1))
            mclass <- optional (peekList peekText (nthBottom 2))
            mattribs <- optional (peekAttribs (nthBottom 3))
            return ( fromMaybe "" mident
                   , fromMaybe [] mclass
                   , fromMaybe [] mattribs)
          TypeTable  -> forcePeek $ peekAttrTable (nthBottom 1)
          TypeUserdata -> forcePeek $ peekUD typeAttr (nthBottom 1) <|> do
            attrList <- peekUD typeAttributeList (nthBottom 1)
            return ("", [], attrList)
          TypeNil    -> pure nullAttr
          TypeNone   -> pure nullAttr
          x          -> failLua $ "Cannot create Attr from " ++ show x)
  =#> functionResult pushAttr "Attr" "new Attr object"

-- | Constructor for 'AttributeList'.
mkAttributeList :: LuaError e => DocumentedFunction e
mkAttributeList = defun "AttributeList"
  ### return
  <#> parameter peekAttribs "table|AttributeList" "attribs" "an attribute list"
  =#> functionResult (pushUD typeAttributeList) "AttributeList"
        "new AttributeList object"