aboutsummaryrefslogtreecommitdiff
path: root/pandoc-lua-engine
diff options
context:
space:
mode:
authorAlbert Krewinkel <[email protected]>2024-10-14 07:21:08 +0200
committerAlbert Krewinkel <[email protected]>2024-10-14 07:53:12 +0200
commitd39994375924a29fc8c518acc9fee7a936f14a31 (patch)
treea8c7b0d45dd068313ae559ac74088d1dd0191580 /pandoc-lua-engine
parent734227a59d416e4512f418468c714b59585cb5e2 (diff)
Lua: Remove prefixes from Lua type names
Lua type names were inconsistent with regard to the use of prefixes; all prefixes are removed now, and Lua types now have the same name as the Haskell types. The use of app-specific prefixes is suggested by the Lua manual to avoid collisions. However, this shouldn't be a problem with pandoc, as it cannot be used as a Lua package. Closes: #8574
Diffstat (limited to 'pandoc-lua-engine')
-rw-r--r--pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/Chunks.hs4
-rw-r--r--pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/CommonState.hs2
-rw-r--r--pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/LogMessage.hs2
-rw-r--r--pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/Sources.hs4
-rw-r--r--pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/Template.hs2
-rw-r--r--pandoc-lua-engine/test/lua/module/pandoc-structure.lua2
-rw-r--r--pandoc-lua-engine/test/lua/module/pandoc-template.lua6
7 files changed, 11 insertions, 11 deletions
diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/Chunks.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/Chunks.hs
index 33c2a92c2..70209f45b 100644
--- a/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/Chunks.hs
+++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/Chunks.hs
@@ -30,7 +30,7 @@ pushChunk :: LuaError e => Pusher e Chunk
pushChunk = pushUD typeChunk
typeChunk :: LuaError e => DocumentedType e Chunk
-typeChunk = deftype "pandoc.Chunk"
+typeChunk = deftype "Chunk"
[ operation Tostring $ lambda
### liftPure show
<#> udparam typeChunk "chunk" "chunk to print in native format"
@@ -103,7 +103,7 @@ pushChunkedDoc = pushUD typeChunkedDoc
-- | Lua type for 'ChunkedDoc' values.
typeChunkedDoc :: LuaError e => DocumentedType e ChunkedDoc
-typeChunkedDoc = deftype "pandoc.ChunkedDoc"
+typeChunkedDoc = deftype "ChunkedDoc"
[]
[ readonly "chunks"
"list of chunks that make up the document"
diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/CommonState.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/CommonState.hs
index f4abd575d..b0d2b0990 100644
--- a/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/CommonState.hs
+++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/CommonState.hs
@@ -22,7 +22,7 @@ import Text.Pandoc.Lua.Marshal.LogMessage (pushLogMessage)
-- | Lua type used for the @CommonState@ object.
typeCommonState :: LuaError e => DocumentedType e CommonState
-typeCommonState = deftype "pandoc CommonState" []
+typeCommonState = deftype "CommonState" []
[ readonly "input_files" "input files passed to pandoc"
(pushPandocList pushString, stInputFiles)
diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/LogMessage.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/LogMessage.hs
index ebc8abb39..752f136f7 100644
--- a/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/LogMessage.hs
+++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/LogMessage.hs
@@ -19,7 +19,7 @@ import qualified Data.Aeson as Aeson
-- | Type definition for pandoc log messages.
typeLogMessage :: LuaError e => DocumentedType e LogMessage
-typeLogMessage = deftype "pandoc LogMessage"
+typeLogMessage = deftype "LogMessage"
[ operation Index $ defun "__tostring"
### liftPure showLogMessage
<#> udparam typeLogMessage "msg" "object"
diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/Sources.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/Sources.hs
index 8224786f6..902c127f2 100644
--- a/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/Sources.hs
+++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/Sources.hs
@@ -25,7 +25,7 @@ import Text.Parsec (SourcePos, sourceName)
pushSources :: LuaError e => Pusher e Sources
pushSources (Sources srcs) = do
pushList (pushUD typeSource) srcs
- newListMetatable "pandoc Sources" $ do
+ newListMetatable "Sources" $ do
pushName "__tostring"
pushHaskellFunction $ do
sources <- forcePeek $ peekList (peekUD typeSource) (nthBottom 1)
@@ -43,7 +43,7 @@ peekSources idx = liftLua (ltype idx) >>= \case
-- | Source object type.
typeSource :: LuaError e => DocumentedType e (SourcePos, Text)
-typeSource = deftype "pandoc input source"
+typeSource = deftype "Source"
[ operation Tostring $ lambda
### liftPure snd
<#> udparam typeSource "srcs" "Source to print in native format"
diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/Template.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/Template.hs
index 8179d6504..d0c29b71d 100644
--- a/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/Template.hs
+++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/Template.hs
@@ -40,4 +40,4 @@ peekTemplate idx = liftLua (ltype idx) >>= \case
-- | Template object type.
typeTemplate :: LuaError e => DocumentedType e (Template Text)
-typeTemplate = deftype "pandoc Template" [] []
+typeTemplate = deftype "Template" [] []
diff --git a/pandoc-lua-engine/test/lua/module/pandoc-structure.lua b/pandoc-lua-engine/test/lua/module/pandoc-structure.lua
index af19785c9..ff2abba22 100644
--- a/pandoc-lua-engine/test/lua/module/pandoc-structure.lua
+++ b/pandoc-lua-engine/test/lua/module/pandoc-structure.lua
@@ -59,7 +59,7 @@ return {
test('returns a chunked doc', function ()
assert.are_equal(
pandoc.utils.type(structure.split_into_chunks(pandoc.Pandoc{})),
- 'pandoc.ChunkedDoc'
+ 'ChunkedDoc'
)
end),
},
diff --git a/pandoc-lua-engine/test/lua/module/pandoc-template.lua b/pandoc-lua-engine/test/lua/module/pandoc-template.lua
index 65e0798f5..36120159a 100644
--- a/pandoc-lua-engine/test/lua/module/pandoc-template.lua
+++ b/pandoc-lua-engine/test/lua/module/pandoc-template.lua
@@ -55,14 +55,14 @@ return {
test('returns a Template', function ()
assert.are_equal(
pandoc.utils.type(template.compile('$title$')),
- 'pandoc Template'
+ 'Template'
)
end),
test('returns a Template', function ()
local templ_path = pandoc.path.join{'lua', 'module', 'default.test'}
assert.are_equal(
pandoc.utils.type(template.compile('${ partial() }', templ_path)),
- 'pandoc Template'
+ 'Template'
)
end),
test('fails if template has non-existing partial', function ()
@@ -76,7 +76,7 @@ return {
assert.are_equal(type(jats_template), 'string')
assert.are_equal(
pandoc.utils.type(template.compile(jats_template)),
- 'pandoc Template'
+ 'Template'
)
end),
},