aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Lua
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Lua')
-rw-r--r--src/Text/Pandoc/Lua/Init.hs1
-rw-r--r--src/Text/Pandoc/Lua/StackInstances.hs94
2 files changed, 69 insertions, 26 deletions
diff --git a/src/Text/Pandoc/Lua/Init.hs b/src/Text/Pandoc/Lua/Init.hs
index 35611d481..8449d736d 100644
--- a/src/Text/Pandoc/Lua/Init.hs
+++ b/src/Text/Pandoc/Lua/Init.hs
@@ -111,6 +111,7 @@ putConstructorsInRegistry = do
constrsToReg $ Pandoc.MetaList mempty
constrsToReg $ Pandoc.Citation mempty mempty mempty Pandoc.AuthorInText 0 0
putInReg "Attr" -- used for Attr type alias
+ putInReg "ListAttributes" -- used for ListAttributes type alias
Lua.pop 1
where
constrsToReg :: Data a => a -> Lua ()
diff --git a/src/Text/Pandoc/Lua/StackInstances.hs b/src/Text/Pandoc/Lua/StackInstances.hs
index 931b8c225..2d7b9c583 100644
--- a/src/Text/Pandoc/Lua/StackInstances.hs
+++ b/src/Text/Pandoc/Lua/StackInstances.hs
@@ -36,9 +36,10 @@ module Text.Pandoc.Lua.StackInstances () where
import Prelude
import Control.Applicative ((<|>))
-import Control.Monad (when)
import Data.Data (showConstr, toConstr)
import Foreign.Lua (Lua, Peekable, Pushable, StackIndex)
+import Foreign.Lua.Userdata ( ensureUserdataMetatable, pushAnyWithMetatable
+ , metatableName)
import Text.Pandoc.Definition
import Text.Pandoc.Extensions (Extensions)
import Text.Pandoc.Lua.Util (defineHowTo, pushViaConstructor)
@@ -185,7 +186,8 @@ pushBlock = \case
Header lvl attr inlns -> pushViaConstructor "Header" lvl inlns (LuaAttr attr)
HorizontalRule -> pushViaConstructor "HorizontalRule"
LineBlock blcks -> pushViaConstructor "LineBlock" blcks
- OrderedList lstAttr list -> pushViaConstructor "OrderedList" list lstAttr
+ OrderedList lstAttr list -> pushViaConstructor "OrderedList" list
+ (LuaListAttributes lstAttr)
Null -> pushViaConstructor "Null"
Para blcks -> pushViaConstructor "Para" blcks
Plain blcks -> pushViaConstructor "Plain" blcks
@@ -207,7 +209,9 @@ peekBlock idx = defineHowTo "get Block value" $ do
<$> elementContent
"HorizontalRule" -> return HorizontalRule
"LineBlock" -> LineBlock <$> elementContent
- "OrderedList" -> uncurry OrderedList <$> elementContent
+ "OrderedList" -> (\(LuaListAttributes lstAttr, lst) ->
+ OrderedList lstAttr lst)
+ <$> elementContent
"Null" -> return Null
"Para" -> Para <$> elementContent
"Plain" -> Plain <$> elementContent
@@ -289,29 +293,44 @@ instance Pushable LuaAttr where
instance Peekable LuaAttr where
peek idx = defineHowTo "get Attr value" (LuaAttr <$> Lua.peek idx)
+-- | Wrapper for ListAttributes
+newtype LuaListAttributes = LuaListAttributes ListAttributes
+
+instance Pushable LuaListAttributes where
+ push (LuaListAttributes (start, style, delimiter)) =
+ pushViaConstructor "ListAttributes" start style delimiter
+
+instance Peekable LuaListAttributes where
+ peek = defineHowTo "get ListAttributes value" .
+ fmap LuaListAttributes . Lua.peek
+
--
-- Hierarchical elements
--
instance Pushable Element where
push (Blk blk) = Lua.push blk
- push (Sec lvl num attr label contents) = do
- Lua.newtable
- LuaUtil.addField "level" lvl
- LuaUtil.addField "numbering" num
- LuaUtil.addField "attr" (LuaAttr attr)
- LuaUtil.addField "label" label
- LuaUtil.addField "contents" contents
- pushSecMetaTable
- Lua.setmetatable (-2)
- where
- pushSecMetaTable :: Lua ()
- pushSecMetaTable = do
- inexistant <- Lua.newmetatable "PandocElementSec"
- when inexistant $ do
- LuaUtil.addField "t" "Sec"
- Lua.push "__index"
- Lua.pushvalue (-2)
- Lua.rawset (-3)
+ push sec = pushAnyWithMetatable pushElementMetatable sec
+ where
+ pushElementMetatable = ensureUserdataMetatable (metatableName sec) $
+ LuaUtil.addFunction "__index" indexElement
+
+instance Peekable Element where
+ peek idx = Lua.ltype idx >>= \case
+ Lua.TypeUserdata -> Lua.peekAny idx
+ _ -> Blk <$> Lua.peek idx
+
+indexElement :: Element -> String -> Lua Lua.NumResults
+indexElement = \case
+ (Blk _) -> const (1 <$ Lua.pushnil) -- this shouldn't happen
+ (Sec lvl num attr label contents) -> fmap (return 1) . \case
+ "level" -> Lua.push lvl
+ "numbering" -> Lua.push num
+ "attr" -> Lua.push (LuaAttr attr)
+ "label" -> Lua.push label
+ "contents" -> Lua.push contents
+ "tag" -> Lua.push "Sec"
+ "t" -> Lua.push "Sec"
+ _ -> Lua.pushnil
--
@@ -340,9 +359,32 @@ instance Pushable ReaderOptions where
LuaUtil.addField "extensions" extensions
LuaUtil.addField "standalone" standalone
LuaUtil.addField "columns" columns
- LuaUtil.addField "tabStop" tabStop
- LuaUtil.addField "indentedCodeClasses" indentedCodeClasses
+ LuaUtil.addField "tab_stop" tabStop
+ LuaUtil.addField "indented_code_classes" indentedCodeClasses
LuaUtil.addField "abbreviations" abbreviations
- LuaUtil.addField "defaultImageExtension" defaultImageExtension
- LuaUtil.addField "trackChanges" trackChanges
- LuaUtil.addField "stripComments" stripComments
+ LuaUtil.addField "default_image_extension" defaultImageExtension
+ LuaUtil.addField "track_changes" trackChanges
+ LuaUtil.addField "strip_comments" stripComments
+
+ -- add metatable
+ let indexReaderOptions :: AnyValue -> AnyValue -> Lua Lua.NumResults
+ indexReaderOptions _tbl (AnyValue key) = do
+ Lua.ltype key >>= \case
+ Lua.TypeString -> Lua.peek key >>= \case
+ "defaultImageExtension" -> Lua.push defaultImageExtension
+ "indentedCodeClasses" -> Lua.push indentedCodeClasses
+ "stripComments" -> Lua.push stripComments
+ "tabStop" -> Lua.push tabStop
+ "trackChanges" -> Lua.push trackChanges
+ _ -> Lua.pushnil
+ _ -> Lua.pushnil
+ return 1
+ Lua.newtable
+ LuaUtil.addFunction "__index" indexReaderOptions
+ Lua.setmetatable (Lua.nthFromTop 2)
+
+-- | Dummy type to allow values of arbitrary Lua type.
+newtype AnyValue = AnyValue StackIndex
+
+instance Peekable AnyValue where
+ peek = return . AnyValue