aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorAlbert Krewinkel <albert@zeitkraut.de>2021-10-26 14:40:11 +0200
committerAlbert Krewinkel <albert@zeitkraut.de>2021-10-26 14:40:11 +0200
commit80ed81822e27ac0d09e365ccc6f6508f3b1b4a9b (patch)
treecab97f694f39d7ee31385592548289232c14bf91
parentf56d8706312df64d3956cea0c93768b51192958e (diff)
downloadpandoc-80ed81822e27ac0d09e365ccc6f6508f3b1b4a9b.tar.gz
Lua: generate constants in module pandoc programmatically
-rw-r--r--data/pandoc.lua80
-rw-r--r--src/Text/Pandoc/Lua/Module/Pandoc.hs17
2 files changed, 17 insertions, 80 deletions
diff --git a/data/pandoc.lua b/data/pandoc.lua
index 2bbf0213e..294fed99e 100644
--- a/data/pandoc.lua
+++ b/data/pandoc.lua
@@ -372,86 +372,6 @@ M.SimpleTable = function(caption, aligns, widths, headers, rows)
}
end
-
-------------------------------------------------------------------------
--- Constants
--- @section constants
-
---- Author name is mentioned in the text.
--- @see Citation
--- @see Cite
-M.AuthorInText = "AuthorInText"
-
---- Author name is suppressed.
--- @see Citation
--- @see Cite
-M.SuppressAuthor = "SuppressAuthor"
-
---- Default citation style is used.
--- @see Citation
--- @see Cite
-M.NormalCitation = "NormalCitation"
-
---- Table cells aligned left.
--- @see Table
-M.AlignLeft = "AlignLeft"
-
---- Table cells right-aligned.
--- @see Table
-M.AlignRight = "AlignRight"
-
---- Table cell content is centered.
--- @see Table
-M.AlignCenter = "AlignCenter"
-
---- Table cells are alignment is unaltered.
--- @see Table
-M.AlignDefault = "AlignDefault"
-
---- Default list number delimiters are used.
--- @see OrderedList
-M.DefaultDelim = "DefaultDelim"
-
---- List numbers are delimited by a period.
--- @see OrderedList
-M.Period = "Period"
-
---- List numbers are delimited by a single parenthesis.
--- @see OrderedList
-M.OneParen = "OneParen"
-
---- List numbers are delimited by a double parentheses.
--- @see OrderedList
-M.TwoParens = "TwoParens"
-
---- List are numbered in the default style
--- @see OrderedList
-M.DefaultStyle = "DefaultStyle"
-
---- List items are numbered as examples.
--- @see OrderedList
-M.Example = "Example"
-
---- List are numbered using decimal integers.
--- @see OrderedList
-M.Decimal = "Decimal"
-
---- List are numbered using lower-case roman numerals.
--- @see OrderedList
-M.LowerRoman = "LowerRoman"
-
---- List are numbered using upper-case roman numerals
--- @see OrderedList
-M.UpperRoman = "UpperRoman"
-
---- List are numbered using lower-case alphabetic characters.
--- @see OrderedList
-M.LowerAlpha = "LowerAlpha"
-
---- List are numbered using upper-case alphabetic characters.
--- @see OrderedList
-M.UpperAlpha = "UpperAlpha"
-
------------------------------------------------------------------------
-- Functions which have moved to different modules
M.sha1 = utils.sha1
diff --git a/src/Text/Pandoc/Lua/Module/Pandoc.hs b/src/Text/Pandoc/Lua/Module/Pandoc.hs
index 340c324ad..458795029 100644
--- a/src/Text/Pandoc/Lua/Module/Pandoc.hs
+++ b/src/Text/Pandoc/Lua/Module/Pandoc.hs
@@ -1,5 +1,6 @@
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{- |
Module : Text.Pandoc.Lua.Module.Pandoc
@@ -20,8 +21,10 @@ import Control.Applicative ((<|>), optional)
import Control.Monad ((>=>), (<$!>), forM_, when)
import Control.Monad.Catch (catch, throwM)
import Control.Monad.Except (throwError)
+import Data.Data (Data, dataTypeConstrs, dataTypeOf, showConstr)
import Data.Default (Default (..))
import Data.Maybe (fromMaybe)
+import Data.Proxy (Proxy (Proxy))
import Data.Text (Text)
import HsLua as Lua hiding (Div, pushModule)
import HsLua.Class.Peekable (PeekError)
@@ -87,6 +90,9 @@ pushModule = do
pop 1 -- remaining constructor table
addConstructorTable (blockConstructors @PandocError)
addConstructorTable (inlineConstructors @PandocError)
+ -- Add string constants
+ forM_ stringConstants $ \c -> do
+ pushString c *> pushString c *> rawset (nth 3)
return 1
inlineConstructors :: LuaError e => [DocumentedFunction e]
@@ -307,6 +313,17 @@ otherConstructors =
, mkListAttributes
]
+stringConstants :: [String]
+stringConstants =
+ let constrs :: forall a. Data a => Proxy a -> [String]
+ constrs _ = map showConstr . dataTypeConstrs . dataTypeOf @a $ undefined
+ in constrs (Proxy @ListNumberStyle)
+ ++ constrs (Proxy @ListNumberDelim)
+ ++ constrs (Proxy @QuoteType)
+ ++ constrs (Proxy @MathType)
+ ++ constrs (Proxy @Alignment)
+ ++ constrs (Proxy @CitationMode)
+
walkElement :: (Walkable (SingletonsList Inline) a,
Walkable (SingletonsList Block) a,
Walkable (List Inline) a,