aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Lua/Module/Types.hs
blob: 4b37dafd9bf65f4b2b69362f05dc4e05bd9faddf (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
{-# LANGUAGE OverloadedStrings #-}
{- |
   Module      : Text.Pandoc.Lua.Module.Types
   Copyright   : © 2019-2021 Albert Krewinkel
   License     : GNU GPL, version 2 or above

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

Pandoc data type constructors.
-}
module Text.Pandoc.Lua.Module.Types
  ( documentedModule
  ) where

import HsLua ( LuaE, NumResults, Peeker, Pusher, Module (..), Field (..)
             , defun, functionResult, parameter, (###), (<#>), (=#>))
import HsLua.Module.Version (peekVersionFuzzy, pushVersion)
import Text.Pandoc.Error (PandocError)
import Text.Pandoc.Lua.ErrorConversion ()
import Text.Pandoc.Lua.Marshaling.AST

import qualified HsLua as Lua

-- | Push the pandoc.types module on the Lua stack.
documentedModule :: Module PandocError
documentedModule = Module
  { moduleName = "pandoc.types"
  , moduleDescription =
      "Constructors for types that are not part of the pandoc AST."
  , moduleFields =
    [ Field
      { fieldName = "clone"
      , fieldDescription = "DEPRECATED! Helper functions for element cloning."
      , fieldPushValue = do
          Lua.newtable
          addFunction "Meta" $ cloneWith peekMeta pushMeta
          addFunction "MetaValue" $ cloneWith peekMetaValue pushMetaValue
      }
    ]
  , moduleFunctions =
      [ defun "Version"
        ### return
        <#> parameter peekVersionFuzzy "string|integer|{integer,...}|Version"
              "version_specifier"
              (mconcat [ "either a version string like `'2.7.3'`, "
                       , "a single integer like `2`, "
                       , "list of integers like `{2,7,3}`, "
                       , "or a Version object"
                       ])
        =#> functionResult pushVersion "Version" "A new Version object."
      ]
  , moduleOperations = []
  }
 where addFunction name fn = do
         Lua.pushName name
         Lua.pushHaskellFunction fn
         Lua.rawset (Lua.nth 3)

cloneWith :: Peeker PandocError a
          -> Pusher PandocError a
          -> LuaE PandocError NumResults
cloneWith peeker pusher = do
  x <- Lua.forcePeek $ peeker (Lua.nthBottom 1)
  pusher x
  return (Lua.NumResults 1)